ghc-7.8.4: The GHC API

Safe HaskellNone
LanguageHaskell98

HsBinds

Synopsis

Documentation

data HsLocalBindsLR idL idR Source

Bindings in a 'let' expression or a 'where' clause

Instances

(Data idL, Data idR) => Data (HsLocalBindsLR idL idR) 
(OutputableBndr idL, OutputableBndr idR) => Outputable (HsLocalBindsLR idL idR) 
Typeable (* -> * -> *) HsLocalBindsLR 

data HsValBindsLR idL idR Source

Value bindings (not implicit parameters)

Constructors

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.

Instances

(Data idL, Data idR) => Data (HsValBindsLR idL idR) 
(OutputableBndr idL, OutputableBndr idR) => Outputable (HsValBindsLR idL idR) 
Typeable (* -> * -> *) HsValBindsLR 

type LHsBind id = LHsBindLR id id Source

type LHsBinds id = LHsBindsLR id id Source

type HsBind id = HsBindLR id id Source

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 (LHsExpr 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

The pattern is never a simple variable; That case is done by FunBind

Fields

pat_lhs :: LPat idL
 
pat_rhs :: GRHSs idR (LHsExpr idR)
 
pat_rhs_ty :: PostTcType

Type of the GRHSs

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

Dictionary binding and suchlike. All VarBinds are introduced by the type checker

Fields

var_id :: idL
 
var_rhs :: LHsExpr idR

Located only for consistency

var_inline :: Bool

True = inline this binding regardless (used for implication constraints only)

AbsBinds 

Fields

abs_tvs :: [TyVar]
 
abs_ev_vars :: [EvVar]

Includes equality constraints

abs_exports :: [ABExport idL]

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

abs_ev_binds :: TcEvBinds

Evidence bindings

abs_binds :: LHsBinds idL

Typechecked user bindings

PatSynBind 

Fields

patsyn_id :: Located idL

Name of the pattern synonym

bind_fvs :: NameSet

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

patsyn_args :: HsPatSynDetails (Located idR)

Formal parameter names

patsyn_def :: LPat idR

Right-hand side

patsyn_dir :: HsPatSynDir idR

Directionality

Instances

(Data idL, Data idR) => Data (HsBindLR idL idR) 
(OutputableBndr idL, OutputableBndr idR) => Outputable (HsBindLR idL idR) 
Typeable (* -> * -> *) HsBindLR 

data ABExport id Source

Constructors

ABE 

Fields

abe_poly :: id

Any INLINE pragmas is attached to this Id

abe_mono :: id
 
abe_wrap :: HsWrapper

See Note [AbsBinds wrappers] Shape: (forall abs_tvs. abs_ev_vars => abe_mono) ~ abe_poly

abe_prags :: TcSpecPrags

SPECIALISE pragmas

Instances

placeHolderNames :: NameSet Source

Used for the NameSet in FunBind and PatBind prior to the renamer

data HsIPBinds id Source

Constructors

IPBinds [LIPBind id] TcEvBinds 

Instances

type LIPBind id = Located (IPBind id) Source

data IPBind id Source

Implicit parameter bindings.

Constructors

IPBind (Either HsIPName id) (LHsExpr id) 

Instances

Data id => Data (IPBind id) 
OutputableBndr id => Outputable (IPBind id) 
Typeable (* -> *) IPBind 

type LSig name = Located (Sig name) Source

data Sig name Source

Signatures and pragmas

Constructors

TypeSig [Located name] (LHsType name)

An ordinary type signature f :: Num a => a -> a

PatSynSig (Located name) (HsPatSynDetails (LHsType name)) (LHsType name) (LHsContext name) (LHsContext name)

A pattern synonym type signature @pattern (Eq b) => P a b :: (Num a) => T a

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

MinimalSig (BooleanFormula (Located name))

A minimal complete definition pragma

{-# MINIMAL a | (b, c | (d | e)) #-}

Instances

Data name => Data (Sig name) 
OutputableBndr name => Outputable (Sig name) 
Typeable (* -> *) Sig 

type LFixitySig name = Located (FixitySig name) Source

data FixitySig name Source

Constructors

FixitySig (Located name) Fixity 

Instances

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

Constructors

IsDefaultMethod

Super-specialised: a default method should be macro-expanded at every call site

SpecPrags [LTcSpecPrag] 

data TcSpecPrag Source

Constructors

SpecPrag Id HsWrapper InlinePragma

The Id to be specialised, an wrapper that specialises the polymorphic function, and inlining spec for the specialised function

hsSigDoc :: Sig name -> SDoc Source

ppr_sig :: OutputableBndr name => Sig name -> SDoc Source

data HsPatSynDirLR idL idR Source

Instances

(Data idL, Data idR) => Data (HsPatSynDirLR idL idR) 
Typeable (* -> * -> *) HsPatSynDirLR