ghc-6.10.3: The GHC APIContentsIndex
HsBinds
Synopsis
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 LHsBinds id = Bag (LHsBind id)
type DictBinds id = LHsBinds id
type LHsBind id = Located (HsBind id)
type HsBind id = HsBindLR id id
type LHsBindLR idL idR = Located (HsBindLR idL idR)
type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)
data HsBindLR idL idR
= FunBind {
fun_id :: Located idL
fun_infix :: Bool
fun_matches :: MatchGroup idR
fun_co_fn :: HsWrapper
bind_fvs :: NameSet
fun_tick :: Maybe (Int, [idR])
}
| PatBind {
pat_lhs :: LPat idL
pat_rhs :: GRHSs idR
pat_rhs_ty :: PostTcType
bind_fvs :: NameSet
}
| VarBind {
var_id :: idL
var_rhs :: LHsExpr idR
}
| AbsBinds {
abs_tvs :: [TyVar]
abs_dicts :: [DictId]
abs_exports :: [([TyVar], idL, idL, [LPrag])]
abs_binds :: LHsBinds idL
}
placeHolderNames :: NameSet
pprValBindsForUser :: (OutputableBndr idL, OutputableBndr idR, OutputableBndr id2) => LHsBindsLR idL idR -> [LSig id2] -> SDoc
pprLHsBinds :: (OutputableBndr idL, OutputableBndr idR) => LHsBindsLR idL idR -> SDoc
emptyLocalBinds :: HsLocalBindsLR a b
isEmptyLocalBinds :: HsLocalBindsLR a b -> Bool
isEmptyValBinds :: HsValBindsLR a b -> Bool
emptyValBindsOut :: HsValBindsLR a b
emptyValBindsIn :: HsValBindsLR a b
emptyLHsBinds :: LHsBindsLR idL idR
isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool
plusHsValBinds :: HsValBinds a -> HsValBinds a -> HsValBinds a
ppr_monobind :: (OutputableBndr idL, OutputableBndr idR) => HsBindLR idL idR -> SDoc
data HsIPBinds id = IPBinds [LIPBind id] (DictBinds id)
isEmptyIPBinds :: HsIPBinds id -> Bool
type LIPBind id = Located (IPBind id)
data IPBind id = IPBind (IPName id) (LHsExpr id)
data HsWrapper
= WpHole
| WpCompose HsWrapper HsWrapper
| WpCast Coercion
| WpApp Var
| WpTyApp Type
| WpLam Var
| WpTyLam TyVar
| WpInline
| WpLet (LHsBinds Id)
pprHsWrapper :: SDoc -> HsWrapper -> SDoc
(<.>) :: HsWrapper -> HsWrapper -> HsWrapper
mkWpTyApps :: [Type] -> HsWrapper
mkWpApps :: [Var] -> HsWrapper
mkWpTyLams :: [TyVar] -> HsWrapper
mkWpLams :: [Var] -> HsWrapper
mk_co_fn :: (a -> HsWrapper) -> [a] -> HsWrapper
idHsWrapper :: HsWrapper
isIdHsWrapper :: HsWrapper -> Bool
type LSig name = Located (Sig name)
data Sig name
= TypeSig (Located name) (LHsType name)
| FixSig (FixitySig name)
| InlineSig (Located name) InlineSpec
| SpecSig (Located name) (LHsType name) InlineSpec
| SpecInstSig (LHsType name)
type LFixitySig name = Located (FixitySig name)
data FixitySig name = FixitySig (Located name) Fixity
type LPrag = Located Prag
data Prag
= InlinePrag InlineSpec
| SpecPrag (HsExpr Id) PostTcType InlineSpec
isInlinePrag :: Prag -> Bool
isSpecPrag :: Prag -> Bool
okBindSig :: Sig a -> Bool
okHsBootSig :: Sig a -> Bool
okClsDclSig :: Sig a -> Bool
okInstDclSig :: Sig a -> Bool
sigForThisGroup :: NameSet -> LSig Name -> Bool
sigName :: LSig name -> Maybe name
sigNameNoLoc :: Sig name -> Maybe name
isFixityLSig :: LSig name -> Bool
isVanillaLSig :: LSig name -> Bool
isSpecLSig :: LSig name -> Bool
isSpecInstLSig :: LSig name -> Bool
isPragLSig :: LSig name -> Bool
isInlineLSig :: LSig name -> Bool
hsSigDoc :: Sig name -> SDoc
eqHsSig :: Eq a => LSig a -> LSig a -> Bool
ppr_sig :: OutputableBndr name => Sig name -> SDoc
pragBrackets :: SDoc -> SDoc
pprVarSig :: (Outputable id, Outputable ty) => id -> ty -> SDoc
pprSpec :: (Outputable id, Outputable ty) => id -> ty -> InlineSpec -> SDoc
pprPrag :: Outputable id => id -> LPrag -> SDoc
Documentation
type HsLocalBinds id = HsLocalBindsLR id id
data HsLocalBindsLR idL idR
Constructors
HsValBinds (HsValBindsLR idL idR)
HsIPBinds (HsIPBinds idR)
EmptyLocalBinds
show/hide Instances
type HsValBinds id = HsValBindsLR id id
data HsValBindsLR idL idR
Constructors
ValBindsIn (LHsBindsLR idL idR) [LSig idR]
ValBindsOut [(RecFlag, LHsBinds idL)] [LSig Name]
show/hide Instances
type LHsBinds id = Bag (LHsBind id)
type DictBinds id = LHsBinds id
type LHsBind id = Located (HsBind id)
type HsBind id = HsBindLR id id
type LHsBindLR idL idR = Located (HsBindLR idL idR)
type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)
data HsBindLR idL idR
Constructors
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) = ...

fun_id :: Located idL
fun_infix :: BoolTrue => infix declaration
fun_matches :: MatchGroup idRThe payload
fun_co_fn :: HsWrapperCoercion 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 :: NameSetAfter 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.
PatBind
pat_lhs :: LPat idL
pat_rhs :: GRHSs idR
pat_rhs_ty :: PostTcType
bind_fvs :: NameSet
VarBind
var_id :: idL
var_rhs :: LHsExpr idR
AbsBinds
abs_tvs :: [TyVar]
abs_dicts :: [DictId]
abs_exports :: [([TyVar], idL, idL, [LPrag])]
abs_binds :: LHsBinds idL
show/hide Instances
placeHolderNames :: NameSet
pprValBindsForUser :: (OutputableBndr idL, OutputableBndr idR, OutputableBndr id2) => LHsBindsLR idL idR -> [LSig id2] -> SDoc
pprLHsBinds :: (OutputableBndr idL, OutputableBndr idR) => LHsBindsLR idL idR -> SDoc
emptyLocalBinds :: HsLocalBindsLR a b
isEmptyLocalBinds :: HsLocalBindsLR a b -> Bool
isEmptyValBinds :: HsValBindsLR a b -> Bool
emptyValBindsOut :: HsValBindsLR a b
emptyValBindsIn :: HsValBindsLR a b
emptyLHsBinds :: LHsBindsLR idL idR
isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool
plusHsValBinds :: HsValBinds a -> HsValBinds a -> HsValBinds a
ppr_monobind :: (OutputableBndr idL, OutputableBndr idR) => HsBindLR idL idR -> SDoc
data HsIPBinds id
Constructors
IPBinds [LIPBind id] (DictBinds id)
show/hide Instances
isEmptyIPBinds :: HsIPBinds id -> Bool
type LIPBind id = Located (IPBind id)
data IPBind id
Implicit parameter bindings.
Constructors
IPBind (IPName id) (LHsExpr id)
show/hide Instances
data HsWrapper
Constructors
WpHole
WpCompose HsWrapper HsWrapper
WpCast Coercion
WpApp Var
WpTyApp Type
WpLam Var
WpTyLam TyVar
WpInline
WpLet (LHsBinds Id)
show/hide Instances
pprHsWrapper :: SDoc -> HsWrapper -> SDoc
(<.>) :: HsWrapper -> HsWrapper -> HsWrapper
mkWpTyApps :: [Type] -> HsWrapper
mkWpApps :: [Var] -> HsWrapper
mkWpTyLams :: [TyVar] -> HsWrapper
mkWpLams :: [Var] -> HsWrapper
mk_co_fn :: (a -> HsWrapper) -> [a] -> HsWrapper
idHsWrapper :: HsWrapper
isIdHsWrapper :: HsWrapper -> Bool
type LSig name = Located (Sig name)
data Sig name
Constructors
TypeSig (Located name) (LHsType name)
FixSig (FixitySig name)
InlineSig (Located name) InlineSpec
SpecSig (Located name) (LHsType name) InlineSpec
SpecInstSig (LHsType name)
show/hide Instances
type LFixitySig name = Located (FixitySig name)
data FixitySig name
Constructors
FixitySig (Located name) Fixity
show/hide Instances
type LPrag = Located Prag
data Prag
Constructors
InlinePrag InlineSpec
SpecPrag (HsExpr Id) PostTcType InlineSpec
isInlinePrag :: Prag -> Bool
isSpecPrag :: Prag -> Bool
okBindSig :: Sig a -> Bool
okHsBootSig :: Sig a -> Bool
okClsDclSig :: Sig a -> Bool
okInstDclSig :: Sig a -> Bool
sigForThisGroup :: NameSet -> LSig Name -> Bool
sigName :: LSig name -> Maybe name
sigNameNoLoc :: Sig name -> Maybe name
isFixityLSig :: LSig name -> Bool
isVanillaLSig :: LSig name -> Bool
isSpecLSig :: LSig name -> Bool
isSpecInstLSig :: LSig name -> Bool
isPragLSig :: LSig name -> Bool
isInlineLSig :: LSig name -> Bool
hsSigDoc :: Sig name -> SDoc
eqHsSig :: Eq a => LSig a -> LSig a -> Bool
ppr_sig :: OutputableBndr name => Sig name -> SDoc
pragBrackets :: SDoc -> SDoc
pprVarSig :: (Outputable id, Outputable ty) => id -> ty -> SDoc
pprSpec :: (Outputable id, Outputable ty) => id -> ty -> InlineSpec -> SDoc
pprPrag :: Outputable id => id -> LPrag -> SDoc
Produced by Haddock version 2.4.2