ghc-7.0.4: The GHC API

HsBinds

Synopsis

Documentation

data HsLocalBindsLR idL idR Source

Instances

data HsValBindsLR idL idR Source

Constructors

ValBindsIn (LHsBindsLR idL idR) [LSig idR] 
ValBindsOut [(RecFlag, LHsBinds idL)] [LSig Name] 

Instances

type LHsBinds id = Bag (LHsBind id)Source

type HsBind id = HsBindLR id idSource

type LHsBindLR idL idR = Located (HsBindLR idL idR)Source

type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)Source

data HsBindLR idL idR Source

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) = ...

Fields

fun_id :: Located idL
 
fun_infix :: Bool

True => infix declaration

fun_matches :: MatchGroup idR

The payload

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 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, [Id])

This is the (optional) module-local tick number.

PatBind 

Fields

pat_lhs :: LPat idL
 
pat_rhs :: GRHSs idR
 
pat_rhs_ty :: PostTcType
 
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

VarBind 

Fields

var_id :: idL
 
var_rhs :: LHsExpr idR
 
var_inline :: Bool
 
AbsBinds 

Fields

abs_tvs :: [TyVar]
 
abs_ev_vars :: [EvVar]
 
abs_exports :: [([TyVar], idL, idL, TcSpecPrags)]
 
abs_ev_binds :: TcEvBinds
 
abs_binds :: LHsBinds idL
 

Instances

Typeable2 HsBindLR 
(Data idL, Data idR) => Data (HsBindLR idL idR) 
(OutputableBndr idL, OutputableBndr idR) => Outputable (HsBindLR idL idR) 

data HsIPBinds id Source

Constructors

IPBinds [LIPBind id] TcEvBinds 

data IPBind id Source

Implicit parameter bindings.

Constructors

IPBind (IPName id) (LHsExpr id) 

Instances

data EvBind Source

Constructors

EvBind EvVar EvTerm 

Instances

type LSig name = Located (Sig name)Source

data Sig name Source

Constructors

TypeSig (Located name) (LHsType name) 
IdSig Id 
FixSig (FixitySig name) 
InlineSig (Located name) InlinePragma 
SpecSig (Located name) (LHsType name) InlinePragma 
SpecInstSig (LHsType name) 

Instances

Typeable1 Sig 
Data name => Data (Sig name) 
OutputableBndr name => Outputable (Sig name) 

data FixitySig name Source

Constructors

FixitySig (Located name) Fixity 

Instances

sigName :: LSig name -> Maybe nameSource

sigNameNoLoc :: Sig name -> Maybe nameSource

eqHsSig :: Eq a => LSig a -> LSig a -> BoolSource