ghc-7.4.1: The GHC API

Safe HaskellSafe-Infered

HsDecls

Contents

Description

Abstract syntax of global declarations.

Definitions for: TyDecl and ConDecl, ClassDecl, InstDecl, DefaultDecl and ForeignDecl.

Synopsis

Toplevel declarations

data HsDecl id Source

A Haskell Declaration

Constructors

TyClD (TyClDecl id)

A type or class declaration.

InstD (InstDecl id)

An instance declaration.

DerivD (DerivDecl id) 
ValD (HsBind id) 
SigD (Sig id) 
DefD (DefaultDecl id) 
ForD (ForeignDecl id) 
WarningD (WarnDecl id) 
AnnD (AnnDecl id) 
RuleD (RuleDecl id) 
VectD (VectDecl id) 
SpliceD (SpliceDecl id) 
DocD DocDecl 
QuasiQuoteD (HsQuasiQuote id) 

Instances

Class or type declarations

data TyClDecl name Source

A type or class declaration.

Constructors

ForeignType 

Fields

tcdLName :: Located name

Name of the class

type constructor

Type constructor

tcdExtName :: Maybe FastString
 
TyFamily
type/data family T :: *->*

Fields

tcdFlavour :: FamilyFlavour
 
tcdLName :: Located name

Name of the class

type constructor

Type constructor

tcdTyVars :: [LHsTyVarBndr name]

Class type variables

type variables

Type variables

tcdKind :: Maybe (LHsKind name)
 
TyData

Declares a data type or newtype, giving its construcors data/newtype T a = constrs data/newtype instance T [a] = constrs

Fields

tcdND :: NewOrData
 
tcdCtxt :: LHsContext name

Context...

Context

tcdLName :: Located name

Name of the class

type constructor

Type constructor

tcdTyVars :: [LHsTyVarBndr name]

Class type variables

type variables

Type variables

tcdTyPats :: Maybe [LHsType name]

Type patterns See Note [tcdTyVars and tcdTyPats]

Type patterns. See Note [tcdTyVars and tcdTyPats]

tcdKindSig :: Maybe (LHsKind name)

Optional kind signature.

(Just k) for a GADT-style data, or data instance decl with explicit kind sig

tcdCons :: [LConDecl name]

Data constructors

For data T a = T1 | T2 a the LConDecls all have ResTyH98. For data T a where { T1 :: T a } the LConDecls all have ResTyGADT.

tcdDerivs :: Maybe [LHsType name]

Derivings; Nothing => not specified, Just [] => derive exactly what is asked

These types must be of form forall ab. C ty1 ty2 Typically the foralls and ty args are empty, but they are non-empty for the newtype-deriving case

TySynonym 

Fields

tcdLName :: Located name

Name of the class

type constructor

Type constructor

tcdTyVars :: [LHsTyVarBndr name]

Class type variables

type variables

Type variables

tcdTyPats :: Maybe [LHsType name]

Type patterns See Note [tcdTyVars and tcdTyPats]

Type patterns. See Note [tcdTyVars and tcdTyPats]

tcdSynRhs :: LHsType name

synonym expansion

ClassDecl 

Fields

tcdCtxt :: LHsContext name

Context...

Context

tcdLName :: Located name

Name of the class

type constructor

Type constructor

tcdTyVars :: [LHsTyVarBndr name]

Class type variables

type variables

Type variables

tcdFDs :: [Located (FunDep name)]

Functional deps

tcdSigs :: [LSig name]

Methods' signatures

tcdMeths :: LHsBinds name

Default methods

tcdATs :: [LTyClDecl name]

Associated types; ie only TyFamily

tcdATDefs :: [LTyClDecl name]

Associated type defaults; ie only TySynonym

tcdDocs :: [LDocDecl]

Haddock docs

Instances

type LTyClDecl name = Located (TyClDecl name)Source

type TyClGroup name = [LTyClDecl name]Source

isClassDecl :: TyClDecl name -> BoolSource

type class

isSynDecl :: TyClDecl name -> BoolSource

vanilla Haskell type synonym (ie, not a type instance)

isDataDecl :: TyClDecl name -> BoolSource

True = argument is a data/newtype or data/newtype instance declaration.

isTypeDecl :: TyClDecl name -> BoolSource

type or type instance declaration

isFamilyDecl :: TyClDecl name -> BoolSource

type family declaration

isFamInstDecl :: TyClDecl name -> BoolSource

family instance (types, newtypes, and data types)

tcdName :: TyClDecl name -> nameSource

Instance declarations

data InstDecl name Source

Constructors

InstDecl (LHsType name) (LHsBinds name) [LSig name] [LTyClDecl name] 

Instances

type LInstDecl name = Located (InstDecl name)Source

data NewOrData Source

Constructors

NewType
newtype Blah ...
DataType
data Blah ...

data FamilyFlavour Source

Constructors

TypeFamily
type family ...
DataFamily
data family ...

Standalone deriving declarations

data DerivDecl name Source

Constructors

DerivDecl 

Fields

deriv_type :: LHsType name
 

Instances

RULE declarations

data RuleDecl name Source

Constructors

HsRule RuleName Activation [RuleBndr name] (Located (HsExpr name)) NameSet (Located (HsExpr name)) NameSet 

Instances

type LRuleDecl name = Located (RuleDecl name)Source

data RuleBndr name Source

Constructors

RuleBndr (Located name) 
RuleBndrSig (Located name) (LHsType name) 

Instances

VECTORISE declarations

type LVectDecl name = Located (VectDecl name)Source

default declarations

data DefaultDecl name Source

Constructors

DefaultDecl [LHsType name] 

Instances

Top-level template haskell splice

Foreign function interface declarations

Data-constructor declarations

data ConDecl name Source

Constructors

ConDecl 

Fields

con_name :: Located name

Constructor name. This is used for the DataCon itself, and for the user-callable wrapper Id.

con_explicit :: HsExplicitFlag

Is there an user-written forall? (cf. HsForAllTy)

con_qvars :: [LHsTyVarBndr name]

Type variables. Depending on con_res this describes the following entities

  • ResTyH98: the constructor's *existential* type variables - ResTyGADT: *all* the constructor's quantified type variables

If con_explicit is Implicit, then con_qvars is irrelevant until after renaming.

con_cxt :: LHsContext name

The context. This does not include the "stupid theta" which lives only in the TyData decl.

con_details :: HsConDeclDetails name

The main payload

con_res :: ResType name

Result type of the constructor

con_doc :: Maybe LHsDocString

A possible Haddock comment.

con_old_rec :: Bool

TEMPORARY field; True = user has employed now-deprecated syntax for GADT-style record decl C { blah } :: T a b Remove this when we no longer parse this stuff, and hence do not need to report decprecated use

Instances

type LConDecl name = Located (ConDecl name)Source

data ResType name Source

Constructors

ResTyH98 
ResTyGADT (LHsType name) 

Instances

Document comments

Deprecations

data WarnDecl name Source

Constructors

Warning name WarningTxt 

Instances

type LWarnDecl name = Located (WarnDecl name)Source

Annotations

data AnnDecl name Source

Constructors

HsAnnotation (AnnProvenance name) (Located (HsExpr name)) 

Instances

type LAnnDecl name = Located (AnnDecl name)Source

modifyAnnProvenanceNameM :: Monad m => (before -> m after) -> AnnProvenance before -> m (AnnProvenance after)Source

Grouping

data HsGroup id Source

A HsDecl is categorised into a HsGroup before being fed to the renamer.

Constructors

HsGroup 

Instances