X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FhsSyn%2FHsBinds.lhs;h=702e7365847e962c0759ef691d8cd044cd4f12a5;hp=6a3f1b0fb175802fce569289e64d43bd4dfb44c8;hb=432b9c9322181a3644083e3c19b7e240d90659e7;hpb=3444b48ef7644c235d7f164f8837090dc30c23bb diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 6a3f1b0..702e736 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -81,40 +81,44 @@ type LHsBindLR idL idR = Located (HsBindLR idL idR) type LHsBindsLR idL idR = Bag (LHsBindLR idL idR) data HsBindLR idL idR - = FunBind { -- FunBind is used for both functions f x = e - -- and variables f = \x -> e --- Reason 1: Special case for type inference: see TcBinds.tcMonoBinds --- --- Reason 2: instance decls can only have FunBinds, which is convenient --- If you change this, you'll need to change e.g. rnMethodBinds - --- But note that the form f :: a->a = ... --- parses as a pattern binding, just like --- (f :: a -> a) = ... + = -- | FunBind is used for both functions @f x = e@ + -- and variables @f = \x -> e@ + -- + -- Reason 1: Special case for type inference: see 'TcBinds.tcMonoBinds'. + -- + -- Reason 2: Instance decls can only have FunBinds, which is convenient. + -- If you change this, you'll need to change e.g. rnMethodBinds + -- + -- But note that the form @f :: a->a = ...@ + -- parses as a pattern binding, just like + -- @(f :: a -> a) = ... @ + FunBind { fun_id :: Located idL, - fun_infix :: Bool, -- True => infix declaration + fun_infix :: Bool, -- ^ True => infix declaration - fun_matches :: MatchGroup idR, -- The payload + fun_matches :: MatchGroup idR, -- ^ The payload - fun_co_fn :: HsWrapper, -- Coercion from the type of the MatchGroup to the type of + fun_co_fn :: HsWrapper, -- ^ Coercion from the type of the MatchGroup to the type of -- the Id. Example: + -- @ -- f :: Int -> forall a. a -> a -- f x y = y + -- @ -- Then the MatchGroup will have type (Int -> a' -> a') -- (with a free type variable a'). The coercion will take -- a CoreExpr of this type and convert it to a CoreExpr of -- type Int -> forall a'. a' -> a' -- Notice that the coercion captures the free a'. - bind_fvs :: NameSet, -- After the renamer, this contains a superset of the + bind_fvs :: NameSet, -- ^ After the renamer, this contains a superset of the -- Names of the other binders in this binding group that -- are free in the RHS of the defn -- Before renaming, and after typechecking, -- the field is unused; it's just an error thunk - fun_tick :: Maybe (Int,[idR]) -- This is the (optional) module-local tick number. + fun_tick :: Maybe (Int,[idR]) -- ^ This is the (optional) module-local tick number. } | PatBind { -- The pattern is never a simple variable; @@ -131,8 +135,9 @@ data HsBindLR idL idR } | AbsBinds { -- Binds abstraction; TRANSLATION - abs_tvs :: [TyVar], - abs_dicts :: [DictId], + abs_tvs :: [TyVar], + abs_dicts :: [DictId], -- Includes equality constraints + -- AbsBinds only gets used when idL = idR after renaming, -- but these need to be idL's for the collect... code in HsUtil to have -- the right type @@ -383,13 +388,13 @@ c1 <.> c2 = c1 `WpCompose` c2 mkWpTyApps :: [Type] -> HsWrapper mkWpTyApps tys = mk_co_fn WpTyApp (reverse tys) -mkWpApps :: [Id] -> HsWrapper +mkWpApps :: [Var] -> HsWrapper mkWpApps ids = mk_co_fn WpApp (reverse ids) mkWpTyLams :: [TyVar] -> HsWrapper mkWpTyLams ids = mk_co_fn WpTyLam ids -mkWpLams :: [Id] -> HsWrapper +mkWpLams :: [Var] -> HsWrapper mkWpLams ids = mk_co_fn WpLam ids mk_co_fn :: (a -> HsWrapper) -> [a] -> HsWrapper @@ -421,12 +426,18 @@ type LSig name = Located (Sig name) data Sig name -- Signatures and pragmas = -- An ordinary type signature -- f :: Num a => a -> a - TypeSig (Located name) -- A bog-std type signature - (LHsType name) + TypeSig (Located name) (LHsType name) + + -- A type signature in generated code, notably the code + -- generated for record selectors. We simply record + -- the desired Id itself, replete with its name, type + -- and IdDetails. Otherwise it's just like a type + -- signature: there should be an accompanying binding + | IdSig Id -- An ordinary fixity declaration -- infixl *** 8 - | FixSig (FixitySig name) -- Fixity declaration + | FixSig (FixitySig name) -- An inline pragma -- {#- INLINE f #-} @@ -506,10 +517,17 @@ isFixityLSig :: LSig name -> Bool isFixityLSig (L _ (FixSig {})) = True isFixityLSig _ = False -isVanillaLSig :: LSig name -> Bool +isVanillaLSig :: LSig name -> Bool -- User type signatures +-- A badly-named function, but it's part of the GHCi (used +-- by Haddock) so I don't want to change it gratuitously. isVanillaLSig (L _(TypeSig {})) = True isVanillaLSig _ = False +isTypeLSig :: LSig name -> Bool -- Type signatures +isTypeLSig (L _(TypeSig {})) = True +isTypeLSig (L _(IdSig {})) = True +isTypeLSig _ = False + isSpecLSig :: LSig name -> Bool isSpecLSig (L _(SpecSig {})) = True isSpecLSig _ = False @@ -531,6 +549,7 @@ isInlineLSig _ = False hsSigDoc :: Sig name -> SDoc hsSigDoc (TypeSig {}) = ptext (sLit "type signature") +hsSigDoc (IdSig {}) = ptext (sLit "id signature") hsSigDoc (SpecSig {}) = ptext (sLit "SPECIALISE pragma") hsSigDoc (InlineSig {}) = ptext (sLit "INLINE pragma") hsSigDoc (SpecInstSig {}) = ptext (sLit "SPECIALISE instance pragma") @@ -542,6 +561,7 @@ Signature equality is used when checking for duplicate signatures \begin{code} eqHsSig :: Eq a => LSig a -> LSig a -> Bool eqHsSig (L _ (FixSig (FixitySig n1 _))) (L _ (FixSig (FixitySig n2 _))) = unLoc n1 == unLoc n2 +eqHsSig (L _ (IdSig n1)) (L _ (IdSig n2)) = n1 == n2 eqHsSig (L _ (TypeSig n1 _)) (L _ (TypeSig n2 _)) = unLoc n1 == unLoc n2 eqHsSig (L _ (InlineSig n1 _)) (L _ (InlineSig n2 _)) = unLoc n1 == unLoc n2 -- For specialisations, we don't have equality over @@ -556,6 +576,7 @@ instance (OutputableBndr name) => Outputable (Sig name) where ppr_sig :: OutputableBndr name => Sig name -> SDoc ppr_sig (TypeSig var ty) = pprVarSig (unLoc var) ty +ppr_sig (IdSig id) = pprVarSig id (varType id) ppr_sig (FixSig fix_sig) = ppr fix_sig ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec var ty inl) ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> ppr var)