diff options
author | simonpj <unknown> | 1999-12-20 10:34:37 +0000 |
---|---|---|
committer | simonpj <unknown> | 1999-12-20 10:34:37 +0000 |
commit | e921b2e307532e0f30eefa88b11a124be592bde4 (patch) | |
tree | 4512ea94bc7aff13ccbd13f513ee40bf5beedf88 /ghc/compiler/rename/RnNames.lhs | |
parent | f7989a6dea8c43352f363117d9bb07439953ccdc (diff) | |
download | haskell-e921b2e307532e0f30eefa88b11a124be592bde4.tar.gz |
[project @ 1999-12-20 10:34:27 by simonpj]
This commit implements a substantial re-organisation of the Prelude
It also fixes a couple of small renamer bugs that were reported recently
(notably, Sven pointed out that we weren't reporting
unused imports properly)
My original goal was to get rid of all "orphan" modules (i.e. ones
with instance decls that don't belong either to a tycon or a class
defined in the same module). This should reduce the number of
interface files that have to be read when compiling small Haskell
modules.
But like most expeditions into the Prelude Swamp, it spiraled out
of control. The result is quite satisfactory, though.
GONE AWAY: PrelCCall, PrelNumExtra
NEW: PrelReal, PrelFloat, PrelByteArr, PrelNum.hi-boot
(The extra PrelNum.hi-boot is because of a tiresome thin-air Id, addr2Integer,
which used to be in PrelBase.)
Quite a lot of types have moved from one module to another,
which entails some changes to part of the compiler (PrelInfo, PrelMods) etc,
and there are a few places in the RTS includes and even in the driver
that know about these home modules (alas).
So the rough structure is as follows, in (linearised) dependency order
[this list now appears in PrelBase.lhs]
PrelGHC Has no implementation. It defines built-in things, and
by importing it you bring them into scope.
The source file is PrelGHC.hi-boot, which is just
copied to make PrelGHC.hi
Classes: CCallable, CReturnable
PrelBase Classes: Eq, Ord, Functor, Monad
Types: list, (), Int, Bool, Ordering, Char, String
PrelTup Types: tuples, plus instances for PrelBase classes
PrelShow Class: Show, plus instances for PrelBase/PrelTup types
PrelEnum Class: Enum, plus instances for PrelBase/PrelTup types
PrelMaybe Type: Maybe, plus instances for PrelBase classes
PrelNum Class: Num, plus instances for Int
Type: Integer, plus instances for all classes so far (Eq, Ord, Num, Show)
Integer is needed here because it is mentioned in the signature
of 'fromInteger' in class Num
PrelReal Classes: Real, Integral, Fractional, RealFrac
plus instances for Int, Integer
Types: Ratio, Rational
plus intances for classes so far
Rational is needed here because it is mentioned in the signature
of 'toRational' in class Real
Ix Classes: Ix, plus instances for Int, Bool, Char, Integer, Ordering, tuples
PrelArr Types: Array, MutableArray, MutableVar
Does *not* contain any ByteArray stuff (see PrelByteArr)
Arrays are used by a function in PrelFloat
PrelFloat Classes: Floating, RealFloat
Types: Float, Double, plus instances of all classes so far
This module contains everything to do with floating point.
It is a big module (900 lines)
With a bit of luck, many modules can be compiled without ever reading PrelFloat.hi
PrelByteArr Types: ByteArray, MutableByteArray
We want this one to be after PrelFloat, because it defines arrays
of unboxed floats.
Other Prelude modules are much easier with fewer complex dependencies.
Diffstat (limited to 'ghc/compiler/rename/RnNames.lhs')
-rw-r--r-- | ghc/compiler/rename/RnNames.lhs | 41 |
1 files changed, 22 insertions, 19 deletions
diff --git a/ghc/compiler/rename/RnNames.lhs b/ghc/compiler/rename/RnNames.lhs index d98dc2aca9..176eca3b3e 100644 --- a/ghc/compiler/rename/RnNames.lhs +++ b/ghc/compiler/rename/RnNames.lhs @@ -413,10 +413,9 @@ filterImports mod (Just (want_hiding, import_items)) avails = addErrRn (badImportItemErr mod item) `thenRn_` returnRn Nothing - | dodgy_import = addWarnRn (dodgyImportWarn mod item) `thenRn_` - returnRn (Just (filtered_avail, explicits)) - - | otherwise = returnRn (Just (filtered_avail, explicits)) + | otherwise + = warnCheckRn (okItem item avail) (dodgyImportWarn mod item) `thenRn_` + returnRn (Just (filtered_avail, explicits)) where wanted_occ = rdrNameOcc (ieName item) @@ -432,13 +431,12 @@ filterImports mod (Just (want_hiding, import_items)) avails IEThingAll _ -> True other -> False - dodgy_import = case (item, avail) of - (IEThingAll _, AvailTC _ [n]) -> True - -- This occurs when you import T(..), but - -- only export T abstractly. The single [n] - -- in the AvailTC is the type or class itself - - other -> False + +okItem (IEThingAll _) (AvailTC _ [n]) = False + -- This occurs when you import T(..), but + -- only export T abstractly. The single [n] + -- in the AvailTC is the type or class itself +okItem _ _ = True \end{code} @@ -608,7 +606,10 @@ exportsFromAvail this_mod (Just export_items) = failWithRn acc (exportItemErr ie) | otherwise -- Phew! It's OK! Now to check the occurrence stuff! - = check_occs ie occs export_avail `thenRn` \ occs' -> + + + = warnCheckRn (okItem ie avail) (dodgyExportWarn ie) `thenRn_` + check_occs ie occs export_avail `thenRn` \ occs' -> returnRn (mods, occs', add_avail avails export_avail) where @@ -659,17 +660,20 @@ badImportItemErr mod ie = sep [ptext SLIT("Module"), quotes (pprModuleName mod), ptext SLIT("does not export"), quotes (ppr ie)] -dodgyImportWarn mod (IEThingAll tc) - = sep [ptext SLIT("Module") <+> quotes (pprModuleName mod) - <+> ptext SLIT("exports") <+> quotes (ppr tc), - ptext SLIT("with no constructors/class operations;"), - ptext SLIT("yet it is imported with a (..)")] +dodgyImportWarn mod item = dodgyMsg (ptext SLIT("import")) item +dodgyExportWarn item = dodgyMsg (ptext SLIT("export")) item +dodgyMsg kind item@(IEThingAll tc) + = sep [ ptext SLIT("The") <+> kind <+> ptext SLIT("item") <+> quotes (ppr item), + ptext SLIT("suggests that") <+> quotes (ppr tc) <+> ptext SLIT("has constructor or class methods"), + ptext SLIT("but it has none; it is a type synonym or abstract type or class") ] + modExportErr mod = hsep [ ptext SLIT("Unknown module in export list: module"), quotes (pprModuleName mod)] exportItemErr export_item - = sep [ ptext SLIT("Bad export item"), quotes (ppr export_item)] + = sep [ ptext SLIT("The export item") <+> quotes (ppr export_item), + ptext SLIT("attempts to export constructors or class methods that are not visible here") ] exportClashErr occ_name ie1 ie2 = hsep [ptext SLIT("The export items"), quotes (ppr ie1) @@ -703,5 +707,4 @@ dupFixityDecl rdr_name loc1 loc2 = vcat [ptext SLIT("Multiple fixity declarations for") <+> quotes (ppr rdr_name), ptext SLIT("at ") <+> ppr loc1, ptext SLIT("and") <+> ppr loc2] - \end{code} |