ghc-7.6.2: The GHC API

Safe HaskellNone

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 LHsBind id = LHsBindLR id idSource

type LHsBinds id = LHsBindsLR id idSource

type HsBind id = HsBindLR id idSource

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

type LHsBindLR idL idR = Located (HsBindLR 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 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 the locally-bound free variables of this defn. See Note [Bind free vars]

fun_tick :: Maybe (Tickish Id)

Tick to put on the rhs, if any

PatBind 

Fields

pat_lhs :: LPat idL
 
pat_rhs :: GRHSs idR
 
pat_rhs_ty :: PostTcType
 
bind_fvs :: NameSet

After the renamer, this contains the locally-bound free variables of this defn. See Note [Bind free vars]

pat_ticks :: (Maybe (Tickish Id), [Maybe (Tickish Id)])

Tick to put on the rhs, if any, and ticks to put on the bound variables.

VarBind 

Fields

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

Instances

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

data ABExport id Source

Constructors

ABE 

data HsIPBinds id Source

Constructors

IPBinds [LIPBind id] TcEvBinds 

data IPBind id Source

Implicit parameter bindings.

Constructors

IPBind (Either HsIPName id) (LHsExpr id) 

Instances

type LSig name = Located (Sig name)Source

data Sig name Source

Constructors

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) 

Instances

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

data FixitySig name Source

Constructors

FixitySig (Located name) Fixity 

Instances

pprVarSig :: Outputable id => [id] -> SDoc -> SDocSource