ghc-6.10.4: The GHC APIContentsIndex
HsDecls
Documentation
data HsDecl id
Constructors
TyClD (TyClDecl id)
InstD (InstDecl id)
DerivD (DerivDecl id)
ValD (HsBind id)
SigD (Sig id)
DefD (DefaultDecl id)
ForD (ForeignDecl id)
WarningD (WarnDecl id)
RuleD (RuleDecl id)
SpliceD (SpliceDecl id)
DocD (DocDecl id)
show/hide Instances
type LHsDecl id = Located (HsDecl id)
data TyClDecl name
Constructors
ForeignType
tcdLName :: Located name
tcdExtName :: Maybe FastString
tcdFoType :: FoType
TyFamily
tcdFlavour :: FamilyFlavour
tcdLName :: Located name
tcdTyVars :: [LHsTyVarBndr name]
tcdKind :: Maybe Kind
TyData
tcdND :: NewOrData
tcdCtxt :: LHsContext name
tcdLName :: Located name
tcdTyVars :: [LHsTyVarBndr name]
tcdTyPats :: Maybe [LHsType name]
tcdKindSig :: Maybe Kind
tcdCons :: [LConDecl name]
tcdDerivs :: Maybe [LHsType name]
TySynonym
tcdLName :: Located name
tcdTyVars :: [LHsTyVarBndr name]
tcdTyPats :: Maybe [LHsType name]
tcdSynRhs :: LHsType name
ClassDecl
tcdCtxt :: LHsContext name
tcdLName :: Located name
tcdTyVars :: [LHsTyVarBndr name]
tcdFDs :: [Located (FunDep name)]
tcdSigs :: [LSig name]
tcdMeths :: LHsBinds name
tcdATs :: [LTyClDecl name]
tcdDocs :: [LDocDecl name]
show/hide Instances
type LTyClDecl name = Located (TyClDecl name)
data InstDecl name
Constructors
InstDecl (LHsType name) (LHsBinds name) [LSig name] [LTyClDecl name]
show/hide Instances
type LInstDecl name = Located (InstDecl name)
data DerivDecl name
Constructors
DerivDecl (LHsType name)
show/hide Instances
type LDerivDecl name = Located (DerivDecl name)
data NewOrData
Constructors
NewType
DataType
show/hide Instances
data FamilyFlavour
Constructors
TypeFamily
DataFamily
data RuleDecl name
Constructors
HsRule RuleName Activation [RuleBndr name] (Located (HsExpr name)) NameSet (Located (HsExpr name)) NameSet
show/hide Instances
type LRuleDecl name = Located (RuleDecl name)
data RuleBndr name
Constructors
RuleBndr (Located name)
RuleBndrSig (Located name) (LHsType name)
show/hide Instances
data DefaultDecl name
Constructors
DefaultDecl [LHsType name]
show/hide Instances
type LDefaultDecl name = Located (DefaultDecl name)
data SpliceDecl id
Constructors
SpliceDecl (Located (HsExpr id))
show/hide Instances
data ForeignDecl name
Constructors
ForeignImport (Located name) (LHsType name) ForeignImport
ForeignExport (Located name) (LHsType name) ForeignExport
show/hide Instances
type LForeignDecl name = Located (ForeignDecl name)
data ForeignImport
Constructors
CImport CCallConv Safety FastString FastString CImportSpec
DNImport DNCallSpec
show/hide Instances
data ForeignExport
Constructors
CExport CExportSpec
DNExport
show/hide Instances
data CImportSpec
Constructors
CLabel CLabelString
CFunction CCallTarget
CWrapper
data FoType
Constructors
DNType
show/hide Instances
data ConDecl name
Constructors
ConDecl
con_name :: Located name
con_explicit :: HsExplicitForAll
con_qvars :: [LHsTyVarBndr name]
con_cxt :: LHsContext name
con_details :: HsConDeclDetails name
con_res :: ResType name
con_doc :: Maybe (LHsDoc name)
show/hide Instances
data ResType name
Constructors
ResTyH98
ResTyGADT (LHsType name)
data ConDeclField name
Constructors
ConDeclField
cd_fld_name :: Located name
cd_fld_type :: LBangType name
cd_fld_doc :: Maybe (LHsDoc name)
type LConDecl name = Located (ConDecl name)
type HsConDeclDetails name = HsConDetails (LBangType name) [ConDeclField name]
hsConDeclArgTys :: HsConDeclDetails name -> [LBangType name]
data DocDecl name
Constructors
DocCommentNext (HsDoc name)
DocCommentPrev (HsDoc name)
DocCommentNamed String (HsDoc name)
DocGroup Int (HsDoc name)
show/hide Instances
type LDocDecl name = Located (DocDecl name)
docDeclDoc :: DocDecl name -> HsDoc name
data WarnDecl name
Constructors
Warning name WarningTxt
show/hide Instances
type LWarnDecl name = Located (WarnDecl name)
data HsGroup id
Constructors
HsGroup
hs_valds :: HsValBinds id
hs_tyclds :: [LTyClDecl id]
hs_instds :: [LInstDecl id]
hs_derivds :: [LDerivDecl id]
hs_fixds :: [LFixitySig id]
hs_defds :: [LDefaultDecl id]
hs_fords :: [LForeignDecl id]
hs_warnds :: [LWarnDecl id]
hs_ruleds :: [LRuleDecl id]
hs_docs :: [LDocDecl id]
show/hide Instances
emptyRdrGroup :: HsGroup a
emptyRnGroup :: HsGroup a
appendGroups :: HsGroup a -> HsGroup a -> HsGroup a
tcdName :: TyClDecl name -> name
tyClDeclNames :: Eq name => TyClDecl name -> [Located name]
tyClDeclTyVars :: TyClDecl name -> [LHsTyVarBndr name]
isClassDecl :: TyClDecl name -> Bool
isSynDecl :: TyClDecl name -> Bool
isDataDecl :: TyClDecl name -> Bool
isTypeDecl :: TyClDecl name -> Bool
isFamilyDecl :: TyClDecl name -> Bool
isFamInstDecl :: TyClDecl name -> Bool
countTyClDecls :: [TyClDecl name] -> (Int, Int, Int, Int, Int, Int)
instDeclATs :: InstDecl name -> [LTyClDecl name]
collectRuleBndrSigTys :: [RuleBndr name] -> [LHsType name]
Produced by Haddock version 2.4.2