diff options
author | simonpj <unknown> | 2000-05-25 12:41:22 +0000 |
---|---|---|
committer | simonpj <unknown> | 2000-05-25 12:41:22 +0000 |
commit | 495ef8bd9ef30bffe50ea399b91e3ba09646b59a (patch) | |
tree | b9ee4302d494d28a81879051d9d3e2a7693ec5e8 /ghc/compiler/hsSyn/HsBinds.lhs | |
parent | b5c71bff716366ae888bf120776d3e163c86c60a (diff) | |
download | haskell-495ef8bd9ef30bffe50ea399b91e3ba09646b59a.tar.gz |
[project @ 2000-05-25 12:41:14 by simonpj]
~~~~~~~~~~~~
Apr/May 2000
~~~~~~~~~~~~
This is a pretty big commit! It adds stuff I've been working on
over the last month or so. DO NOT MERGE IT WITH 4.07!
Interface file formats have changed a little; you'll need
to make clean before remaking.
Simon PJ
Recompilation checking
~~~~~~~~~~~~~~~~~~~~~~
Substantial improvement in recompilation checking. The version management
is now entirely internal to GHC. ghc-iface.lprl is dead!
The trick is to generate the new interface file in two steps:
- first convert Types etc to HsTypes etc, and thereby
build a new ParsedIface
- then compare against the parsed (but not renamed) version of the old
interface file
Doing this meant adding code to convert *to* HsSyn things, and to
compare HsSyn things for equality. That is the main tedious bit.
Another improvement is that we now track version info for
fixities and rules, which was missing before.
Interface file reading
~~~~~~~~~~~~~~~~~~~~~~
Make interface files reading more robust.
* If the old interface file is unreadable, don't fail. [bug fix]
* If the old interface file mentions interfaces
that are unreadable, don't fail. [bug fix]
* When we can't find the interface file,
print the directories we are looking in. [feature]
Type signatures
~~~~~~~~~~~~~~~
* New flag -ddump-types to print type signatures
Type pruning
~~~~~~~~~~~~
When importing
data T = T1 A | T2 B | T3 C
it seems excessive to import the types A, B, C as well, unless
the constructors T1, T2 etc are used. A,B,C might be more types,
and importing them may mean reading more interfaces, and so on.
So the idea is that the renamer will just import the decl
data T
unless one of the constructors is used. This turns out to be quite
easy to implement. The downside is that we must make sure the
constructors are always available if they are really needed, so
I regard this as an experimental feature.
Elimininate ThinAir names
~~~~~~~~~~~~~~~~~~~~~~~~~
Eliminate ThinAir.lhs and all its works. It was always a hack, and now
the desugarer carries around an environment I think we can nuke ThinAir
altogether.
As part of this, I had to move all the Prelude RdrName defns from PrelInfo
to PrelMods --- so I renamed PrelMods as PrelNames.
I also had to move the builtinRules so that they are injected by the renamer
(rather than appearing out of the blue in SimplCore). This is if anything simpler.
Miscellaneous
~~~~~~~~~~~~~
* Tidy up the data types involved in Rules
* Eliminate RnEnv.better_provenance; use Name.hasBetterProv instead
* Add Unique.hasKey :: Uniquable a => a -> Unique -> Bool
It's useful in a lot of places
* Fix a bug in interface file parsing for __U[!]
Diffstat (limited to 'ghc/compiler/hsSyn/HsBinds.lhs')
-rw-r--r-- | ghc/compiler/hsSyn/HsBinds.lhs | 80 |
1 files changed, 18 insertions, 62 deletions
diff --git a/ghc/compiler/hsSyn/HsBinds.lhs b/ghc/compiler/hsSyn/HsBinds.lhs index 4e2f98bcbd..1e7f80bfb5 100644 --- a/ghc/compiler/hsSyn/HsBinds.lhs +++ b/ghc/compiler/hsSyn/HsBinds.lhs @@ -14,7 +14,7 @@ import {-# SOURCE #-} HsExpr ( pprExpr, HsExpr ) import {-# SOURCE #-} HsMatches ( pprMatches, Match, pprGRHSs, GRHSs ) -- friends: -import HsTypes ( HsType, cmpHsType ) +import HsTypes ( HsType ) import HsImpExp ( IE(..), ieName ) import CoreSyn ( CoreExpr ) import PprCore () -- Instances for Outputable @@ -265,16 +265,11 @@ data Sig name | FixSig (FixitySig name) -- Fixity declaration - | DeprecSig (Deprecation name) -- DEPRECATED - SrcLoc - -data FixitySig name = FixitySig name Fixity SrcLoc --- We use exported entities for things to deprecate. Cunning trick (hack?): --- `IEModuleContents undefined' is used for module deprecation. -data Deprecation name = Deprecation (IE name) DeprecTxt +data FixitySig name = FixitySig name Fixity SrcLoc -type DeprecTxt = FAST_STRING -- reason/explanation for deprecation +instance Eq name => Eq (FixitySig name) where + (FixitySig n1 f1 _) == (FixitySig n2 f2 _) = n1==n2 && f1==f2 \end{code} \begin{code} @@ -298,14 +293,6 @@ sigForThisGroup ns sig Just n | isUnboundName n -> True -- Don't complain about an unbound name again | otherwise -> n `elemNameSet` ns -sigsForMe :: (name -> Bool) -> [Sig name] -> [Sig name] -sigsForMe f sigs - = filter sig_for_me sigs - where - sig_for_me sig = case sigName sig of - Nothing -> False - Just n -> f n - sigName :: Sig name -> Maybe name sigName (Sig n _ _) = Just n sigName (ClassOpSig n _ _ _ _) = Just n @@ -313,9 +300,6 @@ sigName (SpecSig n _ _) = Just n sigName (InlineSig n _ _) = Just n sigName (NoInlineSig n _ _) = Just n sigName (FixSig (FixitySig n _ _)) = Just n -sigName (DeprecSig (Deprecation d _) _) = case d of - IEModuleContents _ -> Nothing - other -> Just (ieName d) sigName other = Nothing isFixitySig :: Sig name -> Bool @@ -332,7 +316,6 @@ isPragSig (SpecSig _ _ _) = True isPragSig (InlineSig _ _ _) = True isPragSig (NoInlineSig _ _ _) = True isPragSig (SpecInstSig _ _) = True -isPragSig (DeprecSig _ _) = True isPragSig other = False \end{code} @@ -344,7 +327,6 @@ hsSigDoc (InlineSig _ _ loc) = (SLIT("INLINE pragma"),loc) hsSigDoc (NoInlineSig _ _ loc) = (SLIT("NOINLINE pragma"),loc) hsSigDoc (SpecInstSig _ loc) = (SLIT("SPECIALISE instance pragma"),loc) hsSigDoc (FixSig (FixitySig _ _ loc)) = (SLIT("fixity declaration"), loc) -hsSigDoc (DeprecSig _ loc) = (SLIT("DEPRECATED pragma"), loc) \end{code} \begin{code} @@ -355,8 +337,10 @@ ppr_sig :: Outputable name => Sig name -> SDoc ppr_sig (Sig var ty _) = sep [ppr var <+> dcolon, nest 4 (ppr ty)] -ppr_sig (ClassOpSig var _ _ ty _) - = sep [ppr var <+> dcolon, nest 4 (ppr ty)] +ppr_sig (ClassOpSig var _ dm ty _) + = sep [ppr var <+> pp_dm <+> dcolon, nest 4 (ppr ty)] + where + pp_dm = if dm then equals else empty -- Default-method indicator ppr_sig (SpecSig var ty _) = sep [ hsep [text "{-# SPECIALIZE", ppr var, dcolon], @@ -374,17 +358,10 @@ ppr_sig (SpecInstSig ty _) ppr_sig (FixSig fix_sig) = ppr fix_sig -ppr_sig (DeprecSig deprec _) = ppr deprec instance Outputable name => Outputable (FixitySig name) where ppr (FixitySig name fixity loc) = sep [ppr fixity, ppr name] -instance Outputable name => Outputable (Deprecation name) where - ppr (Deprecation (IEModuleContents _) txt) - = hsep [text "{-# DEPRECATED", doubleQuotes (ppr txt), text "#-}"] - ppr (Deprecation thing txt) - = hsep [text "{-# DEPRECATED", ppr thing, doubleQuotes (ppr txt), text "#-}"] - ppr_phase :: Maybe Int -> SDoc ppr_phase Nothing = empty ppr_phase (Just n) = int n @@ -394,37 +371,16 @@ Checking for distinct signatures; oh, so boring \begin{code} -cmpHsSig :: Sig Name -> Sig Name -> Ordering -cmpHsSig (Sig n1 _ _) (Sig n2 _ _) = n1 `compare` n2 -cmpHsSig (DeprecSig (Deprecation ie1 _) _) - (DeprecSig (Deprecation ie2 _) _) = cmp_ie ie1 ie2 -cmpHsSig (InlineSig n1 _ _) (InlineSig n2 _ _) = n1 `compare` n2 -cmpHsSig (NoInlineSig n1 _ _) (NoInlineSig n2 _ _) = n1 `compare` n2 - -cmpHsSig (SpecInstSig ty1 _) (SpecInstSig ty2 _) = cmpHsType compare ty1 ty2 -cmpHsSig (SpecSig n1 ty1 _) (SpecSig n2 ty2 _) +eqHsSig :: Sig Name -> Sig Name -> Bool +eqHsSig (Sig n1 _ _) (Sig n2 _ _) = n1 == n2 +eqHsSig (InlineSig n1 _ _) (InlineSig n2 _ _) = n1 == n2 +eqHsSig (NoInlineSig n1 _ _) (NoInlineSig n2 _ _) = n1 == n2 + +eqHsSig (SpecInstSig ty1 _) (SpecInstSig ty2 _) = ty1 == ty2 +eqHsSig (SpecSig n1 ty1 _) (SpecSig n2 ty2 _) = -- may have many specialisations for one value; -- but not ones that are exactly the same... - thenCmp (n1 `compare` n2) (cmpHsType compare ty1 ty2) - -cmpHsSig other_1 other_2 -- Tags *must* be different - | (sig_tag other_1) _LT_ (sig_tag other_2) = LT - | otherwise = GT - -cmp_ie :: IE Name -> IE Name -> Ordering -cmp_ie (IEVar n1 ) (IEVar n2 ) = n1 `compare` n2 -cmp_ie (IEThingAbs n1 ) (IEThingAbs n2 ) = n1 `compare` n2 -cmp_ie (IEThingAll n1 ) (IEThingAll n2 ) = n1 `compare` n2 --- Hmmm... -cmp_ie (IEThingWith n1 _) (IEThingWith n2 _) = n1 `compare` n2 -cmp_ie (IEModuleContents _ ) (IEModuleContents _ ) = EQ - -sig_tag (Sig n1 _ _) = (ILIT(1) :: FAST_INT) -sig_tag (SpecSig n1 _ _) = ILIT(2) -sig_tag (InlineSig n1 _ _) = ILIT(3) -sig_tag (NoInlineSig n1 _ _) = ILIT(4) -sig_tag (SpecInstSig _ _) = ILIT(5) -sig_tag (FixSig _) = ILIT(6) -sig_tag (DeprecSig _ _) = ILIT(7) -sig_tag _ = panic# "tag(RnBinds)" + (n1 == n2) && (ty1 == ty2) + +eqHsSig other_1 other_2 = False \end{code} |