ghc-7.8.4: The GHC API

Safe HaskellNone
LanguageHaskell98

HsDecls

Contents

Description

Abstract syntax of global declarations.

Definitions for: SynDecl 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) 
RoleAnnotD (RoleAnnotDecl id) 

Instances

Data id => Data (HsDecl id) 
OutputableBndr name => Outputable (HsDecl name) 
Typeable (* -> *) HsDecl 

type LHsDecl id = Located (HsDecl id) Source

data HsDataDefn name Source

Constructors

HsDataDefn

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

Fields

dd_ND :: NewOrData
 
dd_ctxt :: LHsContext name

Context

dd_cType :: Maybe CType
 
dd_kindSig :: Maybe (LHsKind name)

Optional kind signature.

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

Always Nothing for H98-syntax decls

dd_cons :: [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.

dd_derivs :: 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

Instances

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

Class or type declarations

data TyClDecl name Source

A type or class declaration.

Constructors

ForeignType 

Fields

tcdLName :: Located name

Type constructor

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

Fields

tcdFam :: FamilyDecl name
 
SynDecl

type declaration

Fields

tcdLName :: Located name

Type constructor

tcdTyVars :: LHsTyVarBndrs name

Type variables; for an associated type these include outer binders

tcdRhs :: LHsType name

RHS of type declaration

tcdFVs :: NameSet
 
DataDecl

data declaration

Fields

tcdLName :: Located name

Type constructor

tcdTyVars :: LHsTyVarBndrs name

Type variables; for an associated type these include outer binders

tcdDataDefn :: HsDataDefn name
 
tcdFVs :: NameSet
 
ClassDecl 

Fields

tcdCtxt :: LHsContext name

Context...

tcdLName :: Located name

Type constructor

tcdTyVars :: LHsTyVarBndrs name

Type variables; for an associated type these include outer binders

tcdFDs :: [Located (FunDep name)]

Functional deps

tcdSigs :: [LSig name]

Methods' signatures

tcdMeths :: LHsBinds name

Default methods

tcdATs :: [LFamilyDecl name]

Associated types; ie

tcdATDefs :: [LTyFamInstDecl name]

Associated type defaults

tcdDocs :: [LDocDecl]

Haddock docs

tcdFVs :: NameSet
 

Instances

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

type LTyClDecl name = Located (TyClDecl name) Source

data TyClGroup name Source

Constructors

TyClGroup 

Fields

group_tyclds :: [LTyClDecl name]
 
group_roles :: [LRoleAnnotDecl name]
 

Instances

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

isClassDecl :: TyClDecl name -> Bool Source

type class

isDataDecl :: TyClDecl name -> Bool Source

True = argument is a data/newtype declaration.

isSynDecl :: TyClDecl name -> Bool Source

type or type instance declaration

tcdName :: TyClDecl name -> name Source

isFamilyDecl :: TyClDecl name -> Bool Source

type/data family declaration

isTypeFamilyDecl :: TyClDecl name -> Bool Source

type family declaration

isDataFamilyDecl :: TyClDecl name -> Bool Source

data family declaration

isOpenTypeFamilyInfo :: FamilyInfo name -> Bool Source

open type family info

isClosedTypeFamilyInfo :: FamilyInfo name -> Bool Source

closed type family info

data FamilyDecl name Source

Constructors

FamilyDecl 

Fields

fdInfo :: FamilyInfo name
 
fdLName :: Located name
 
fdTyVars :: LHsTyVarBndrs name
 
fdKindSig :: Maybe (LHsKind name)
 

Instances

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

Instance declarations

data InstDecl name Source

Constructors

ClsInstD 

Fields

cid_inst :: ClsInstDecl name
 
DataFamInstD 

Fields

dfid_inst :: DataFamInstDecl name
 
TyFamInstD 

Fields

tfid_inst :: TyFamInstDecl name
 

Instances

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

type LInstDecl name = Located (InstDecl name) Source

data NewOrData Source

Constructors

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

data FamilyInfo name Source

Instances

Data name => Data (FamilyInfo name) 
Outputable (FamilyInfo name) 
Typeable (* -> *) FamilyInfo 

data TyFamInstDecl name Source

Constructors

TyFamInstDecl 

Instances

data DataFamInstDecl name Source

Constructors

DataFamInstDecl 

Fields

dfid_tycon :: Located name
 
dfid_pats :: HsWithBndrs [LHsType name]

Type patterns (with kind and type bndrs) See Note [Family instance declaration binders]

dfid_defn :: HsDataDefn name
 
dfid_fvs :: NameSet
 

Instances

data TyFamInstEqn name Source

One equation in a type family instance declaration

Constructors

TyFamInstEqn 

Fields

tfie_tycon :: Located name
 
tfie_pats :: HsWithBndrs [LHsType name]

Type patterns (with kind and type bndrs) See Note [Family instance declaration binders]

tfie_rhs :: LHsType name
 

Instances

data ClsInstDecl name Source

Constructors

ClsInstDecl 

Instances

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

Standalone deriving declarations

data DerivDecl name Source

Constructors

DerivDecl 

Fields

deriv_type :: LHsType name
 

Instances

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

type LDerivDecl name = Located (DerivDecl name) Source

RULE declarations

data RuleDecl name Source

Constructors

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

Instances

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

type LRuleDecl name = Located (RuleDecl name) Source

data RuleBndr name Source

Constructors

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

Instances

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

VECTORISE declarations

type LVectDecl name = Located (VectDecl name) Source

default declarations

data DefaultDecl name Source

Constructors

DefaultDecl [LHsType name] 

Instances

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

Template haskell declaration splice

data SpliceDecl id Source

Instances

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 :: LHsTyVarBndrs 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 (LHsType 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

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

type LConDecl name = Located (ConDecl name) Source

data ResType ty Source

Constructors

ResTyH98 
ResTyGADT ty 

Instances

Data ty => Data (ResType ty) 
Outputable ty => Outputable (ResType ty) 
Typeable (* -> *) ResType 

Document comments

Deprecations

data WarnDecl name Source

Constructors

Warning name WarningTxt 

Instances

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

type LWarnDecl name = Located (WarnDecl name) Source

Annotations

data AnnDecl name Source

Constructors

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

Instances

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

type LAnnDecl name = Located (AnnDecl name) Source

Role annotations

data RoleAnnotDecl name Source

Constructors

RoleAnnotDecl (Located name) [Located (Maybe Role)] 

Instances

Grouping

data HsGroup id Source

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

Instances

Data id => Data (HsGroup id) 
OutputableBndr name => Outputable (HsGroup name) 
Typeable (* -> *) HsGroup