Safe Haskell | None |
---|
- type HsLocalBinds id = HsLocalBindsLR id id
- data HsLocalBindsLR idL idR
- = HsValBinds (HsValBindsLR idL idR)
- | HsIPBinds (HsIPBinds idR)
- | EmptyLocalBinds
- type HsValBinds id = HsValBindsLR id id
- data HsValBindsLR idL idR
- = ValBindsIn (LHsBindsLR idL idR) [LSig idR]
- | ValBindsOut [(RecFlag, LHsBinds idL)] [LSig Name]
- type LHsBind id = LHsBindLR id id
- type LHsBinds id = LHsBindsLR id id
- type HsBind id = HsBindLR id id
- type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)
- type LHsBindLR idL idR = Located (HsBindLR idL idR)
- data HsBindLR idL idR
- = FunBind { }
- | PatBind { }
- | VarBind {
- var_id :: idL
- var_rhs :: LHsExpr idR
- var_inline :: Bool
- | AbsBinds {
- abs_tvs :: [TyVar]
- abs_ev_vars :: [EvVar]
- abs_exports :: [ABExport idL]
- abs_ev_binds :: TcEvBinds
- abs_binds :: LHsBinds idL
- data ABExport id = ABE {}
- placeHolderNames :: NameSet
- pprLHsBinds :: (OutputableBndr idL, OutputableBndr idR) => LHsBindsLR idL idR -> SDoc
- pprLHsBindsForUser :: (OutputableBndr idL, OutputableBndr idR, OutputableBndr id2) => LHsBindsLR idL idR -> [LSig id2] -> [SDoc]
- pprDeclList :: [SDoc] -> SDoc
- emptyLocalBinds :: HsLocalBindsLR a b
- isEmptyLocalBinds :: HsLocalBindsLR a b -> Bool
- isEmptyValBinds :: HsValBindsLR a b -> Bool
- emptyValBindsIn :: HsValBindsLR a b
- emptyValBindsOut :: HsValBindsLR a b
- emptyLHsBinds :: LHsBindsLR idL idR
- isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool
- plusHsValBinds :: HsValBinds a -> HsValBinds a -> HsValBinds a
- getTypeSigNames :: HsValBinds a -> NameSet
- ppr_monobind :: (OutputableBndr idL, OutputableBndr idR) => HsBindLR idL idR -> SDoc
- pprTicks :: SDoc -> SDoc -> SDoc
- data HsIPBinds id = IPBinds [LIPBind id] TcEvBinds
- isEmptyIPBinds :: HsIPBinds id -> Bool
- type LIPBind id = Located (IPBind id)
- data IPBind id = IPBind (Either HsIPName id) (LHsExpr id)
- type LSig name = Located (Sig name)
- data Sig name
- = TypeSig [Located name] (LHsType name)
- | GenericSig [Located name] (LHsType name)
- | IdSig Id
- | FixSig (FixitySig name)
- | InlineSig (Located name) InlinePragma
- | SpecSig (Located name) (LHsType name) InlinePragma
- | SpecInstSig (LHsType name)
- type LFixitySig name = Located (FixitySig name)
- data FixitySig name = FixitySig (Located name) Fixity
- data TcSpecPrags
- type LTcSpecPrag = Located TcSpecPrag
- data TcSpecPrag = SpecPrag Id HsWrapper InlinePragma
- noSpecPrags :: TcSpecPrags
- hasSpecPrags :: TcSpecPrags -> Bool
- isDefaultMethod :: TcSpecPrags -> Bool
- isFixityLSig :: LSig name -> Bool
- isVanillaLSig :: LSig name -> Bool
- isTypeLSig :: LSig name -> Bool
- isSpecLSig :: LSig name -> Bool
- isSpecInstLSig :: LSig name -> Bool
- isPragLSig :: LSig name -> Bool
- isInlineLSig :: LSig name -> Bool
- hsSigDoc :: Sig name -> SDoc
- ppr_sig :: OutputableBndr name => Sig name -> SDoc
- pragBrackets :: SDoc -> SDoc
- pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc
- pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc
- pprTcSpecPrags :: TcSpecPrags -> SDoc
Documentation
type HsLocalBinds id = HsLocalBindsLR id idSource
data HsLocalBindsLR idL idR Source
Bindings in a 'let' expression or a 'where' clause
HsValBinds (HsValBindsLR idL idR) | |
HsIPBinds (HsIPBinds idR) | |
EmptyLocalBinds |
(Data idL, Data idR) => Data (HsLocalBindsLR idL idR) | |
(OutputableBndr idL, OutputableBndr idR) => Outputable (HsLocalBindsLR idL idR) | |
Typeable (* -> * -> *) HsLocalBindsLR |
type HsValBinds id = HsValBindsLR id idSource
data HsValBindsLR idL idR Source
Value bindings (not implicit parameters)
ValBindsIn (LHsBindsLR idL idR) [LSig idR] | Before renaming RHS; idR is always RdrName Not dependency analysed Recursive by default |
ValBindsOut [(RecFlag, LHsBinds idL)] [LSig Name] | After renaming RHS; idR can be Name or Id Dependency analysed, later bindings in the list may depend on earlier ones. |
(Data idL, Data idR) => Data (HsValBindsLR idL idR) | |
(OutputableBndr idL, OutputableBndr idR) => Outputable (HsValBindsLR idL idR) | |
Typeable (* -> * -> *) HsValBindsLR |
type LHsBinds id = LHsBindsLR id idSource
type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)Source
FunBind | FunBind is used for both functions Reason 1: Special case for type inference: see 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 |
| |
PatBind | The pattern is never a simple variable; That case is done by FunBind |
| |
VarBind | Dictionary binding and suchlike. All VarBinds are introduced by the type checker |
AbsBinds | |
|
(Data idL, Data idR) => Data (HsBindLR idL idR) | |
(OutputableBndr idL, OutputableBndr idR) => Outputable (HsBindLR idL idR) | |
Typeable (* -> * -> *) HsBindLR |
Data id => Data (ABExport id) | |
OutputableBndr id => Outputable (ABExport id) | |
Typeable (* -> *) ABExport |
placeHolderNames :: NameSetSource
Used for the NameSet in FunBind and PatBind prior to the renamer
pprLHsBinds :: (OutputableBndr idL, OutputableBndr idR) => LHsBindsLR idL idR -> SDocSource
pprLHsBindsForUser :: (OutputableBndr idL, OutputableBndr idR, OutputableBndr id2) => LHsBindsLR idL idR -> [LSig id2] -> [SDoc]Source
pprDeclList :: [SDoc] -> SDocSource
isEmptyLocalBinds :: HsLocalBindsLR a b -> BoolSource
isEmptyValBinds :: HsValBindsLR a b -> BoolSource
emptyLHsBinds :: LHsBindsLR idL idRSource
isEmptyLHsBinds :: LHsBindsLR idL idR -> BoolSource
plusHsValBinds :: HsValBinds a -> HsValBinds a -> HsValBinds aSource
getTypeSigNames :: HsValBinds a -> NameSetSource
ppr_monobind :: (OutputableBndr idL, OutputableBndr idR) => HsBindLR idL idR -> SDocSource
Data id => Data (HsIPBinds id) | |
OutputableBndr id => Outputable (HsIPBinds id) | |
Typeable (* -> *) HsIPBinds |
isEmptyIPBinds :: HsIPBinds id -> BoolSource
Implicit parameter bindings.
Data id => Data (IPBind id) | |
OutputableBndr id => Outputable (IPBind id) | |
Typeable (* -> *) IPBind |
Signatures and pragmas
TypeSig [Located name] (LHsType name) | An ordinary type signature
|
GenericSig [Located name] (LHsType name) | A type signature for a default method inside a class default eq :: (Representable0 a, GEq (Rep0 a)) => a -> a -> Bool |
IdSig Id | 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 |
FixSig (FixitySig name) | An ordinary fixity declaration infixl *** 8 |
InlineSig (Located name) InlinePragma | An inline pragma {#- INLINE f #-} |
SpecSig (Located name) (LHsType name) InlinePragma | A specialisation pragma {-# SPECIALISE f :: Int -> Int #-} |
SpecInstSig (LHsType name) | A specialisation pragma for instance declarations only {-# SPECIALISE instance Eq [Int] #-} (Class tys); should be a specialisation of the current instance declaration |
Data name => Data (Sig name) | |
OutputableBndr name => Outputable (Sig name) | |
Typeable (* -> *) Sig |
type LFixitySig name = Located (FixitySig name)Source
Data name => Data (FixitySig name) | |
OutputableBndr name => Outputable (FixitySig name) | |
Typeable (* -> *) FixitySig |
data TcSpecPrags Source
TsSpecPrags conveys pragmas from the type checker to the desugarer
IsDefaultMethod | Super-specialised: a default method should be macro-expanded at every call site |
SpecPrags [LTcSpecPrag] |
type LTcSpecPrag = Located TcSpecPragSource
data TcSpecPrag Source
SpecPrag Id HsWrapper InlinePragma | The Id to be specialised, an wrapper that specialises the polymorphic function, and inlining spec for the specialised function |
isFixityLSig :: LSig name -> BoolSource
isVanillaLSig :: LSig name -> BoolSource
isTypeLSig :: LSig name -> BoolSource
isSpecLSig :: LSig name -> BoolSource
isSpecInstLSig :: LSig name -> BoolSource
isPragLSig :: LSig name -> BoolSource
isInlineLSig :: LSig name -> BoolSource
ppr_sig :: OutputableBndr name => Sig name -> SDocSource
pragBrackets :: SDoc -> SDocSource
pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDocSource
pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDocSource