Safe Haskell | None |
---|---|
Language | Haskell2010 |
IfaceSyn
- module IfaceType
- data IfaceDecl
- = IfaceId {
- ifName :: IfaceTopBndr
- ifType :: IfaceType
- ifIdDetails :: IfaceIdDetails
- ifIdInfo :: IfaceIdInfo
- | IfaceData {
- ifName :: IfaceTopBndr
- ifCType :: Maybe CType
- ifTyVars :: [IfaceTvBndr]
- ifRoles :: [Role]
- ifCtxt :: IfaceContext
- ifCons :: IfaceConDecls
- ifRec :: RecFlag
- ifPromotable :: Bool
- ifGadtSyntax :: Bool
- ifParent :: IfaceTyConParent
- | IfaceSynonym { }
- | IfaceFamily {
- ifName :: IfaceTopBndr
- ifTyVars :: [IfaceTvBndr]
- ifFamKind :: IfaceKind
- ifFamFlav :: IfaceFamTyConFlav
- | IfaceClass {
- ifCtxt :: IfaceContext
- ifName :: IfaceTopBndr
- ifTyVars :: [IfaceTvBndr]
- ifRoles :: [Role]
- ifFDs :: [FunDep FastString]
- ifATs :: [IfaceAT]
- ifSigs :: [IfaceClassOp]
- ifMinDef :: BooleanFormula IfLclName
- ifRec :: RecFlag
- | IfaceAxiom {
- ifName :: IfaceTopBndr
- ifTyCon :: IfaceTyCon
- ifRole :: Role
- ifAxBranches :: [IfaceAxBranch]
- | IfacePatSyn {
- ifName :: IfaceTopBndr
- ifPatIsInfix :: Bool
- ifPatMatcher :: (IfExtName, Bool)
- ifPatBuilder :: Maybe (IfExtName, Bool)
- ifPatUnivTvs :: [IfaceTvBndr]
- ifPatExTvs :: [IfaceTvBndr]
- ifPatProvCtxt :: IfaceContext
- ifPatReqCtxt :: IfaceContext
- ifPatArgs :: [IfaceType]
- ifPatTy :: IfaceType
- = IfaceId {
- data IfaceFamTyConFlav
- data IfaceClassOp = IfaceClassOp IfaceTopBndr DefMethSpec IfaceType
- data IfaceAT = IfaceAT IfaceDecl (Maybe IfaceType)
- data IfaceConDecl = IfCon {
- ifConOcc :: IfaceTopBndr
- ifConWrapper :: Bool
- ifConInfix :: Bool
- ifConExTvs :: [IfaceTvBndr]
- ifConEqSpec :: IfaceEqSpec
- ifConCtxt :: IfaceContext
- ifConArgTys :: [IfaceType]
- ifConFields :: [IfaceTopBndr]
- ifConStricts :: [IfaceBang]
- data IfaceConDecls
- type IfaceEqSpec = [(IfLclName, IfaceType)]
- data IfaceExpr
- = IfaceLcl IfLclName
- | IfaceExt IfExtName
- | IfaceType IfaceType
- | IfaceCo IfaceCoercion
- | IfaceTuple TupleSort [IfaceExpr]
- | IfaceLam IfaceLamBndr IfaceExpr
- | IfaceApp IfaceExpr IfaceExpr
- | IfaceCase IfaceExpr IfLclName [IfaceAlt]
- | IfaceECase IfaceExpr IfaceType
- | IfaceLet IfaceBinding IfaceExpr
- | IfaceCast IfaceExpr IfaceCoercion
- | IfaceLit Literal
- | IfaceFCall ForeignCall IfaceType
- | IfaceTick IfaceTickish IfaceExpr
- type IfaceAlt = (IfaceConAlt, [IfLclName], IfaceExpr)
- data IfaceLetBndr = IfLetBndr IfLclName IfaceType IfaceIdInfo
- data IfaceBinding
- data IfaceConAlt
- data IfaceIdInfo
- = NoInfo
- | HasInfo [IfaceInfoItem]
- data IfaceIdDetails
- data IfaceUnfolding
- data IfaceInfoItem
- data IfaceRule = IfaceRule {}
- data IfaceAnnotation = IfaceAnnotation {}
- type IfaceAnnTarget = AnnTarget OccName
- data IfaceClsInst = IfaceClsInst {}
- data IfaceFamInst = IfaceFamInst {}
- data IfaceTickish
- data IfaceBang
- data IfaceAxBranch = IfaceAxBranch {
- ifaxbTyVars :: [IfaceTvBndr]
- ifaxbLHS :: IfaceTcArgs
- ifaxbRoles :: [Role]
- ifaxbRHS :: IfaceType
- ifaxbIncomps :: [BranchIndex]
- data IfaceTyConParent
- ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName]
- visibleIfConDecls :: IfaceConDecls -> [IfaceConDecl]
- ifaceDeclFingerprints :: Fingerprint -> IfaceDecl -> [(OccName, Fingerprint)]
- freeNamesIfDecl :: IfaceDecl -> NameSet
- freeNamesIfRule :: IfaceRule -> NameSet
- freeNamesIfFamInst :: IfaceFamInst -> NameSet
- pprIfaceExpr :: (SDoc -> SDoc) -> IfaceExpr -> SDoc
- pprIfaceDecl :: ShowSub -> IfaceDecl -> SDoc
- data ShowSub = ShowSub {
- ss_ppr_bndr :: OccName -> SDoc
- ss_how_much :: ShowHowMuch
- data ShowHowMuch
- = ShowHeader
- | ShowSome [OccName]
- | ShowIface
Documentation
module IfaceType
Constructors
Instances
data IfaceFamTyConFlav Source
Constructors
IfaceOpenSynFamilyTyCon | |
IfaceClosedSynFamilyTyCon IfExtName [IfaceAxBranch] | |
IfaceAbstractClosedSynFamilyTyCon | |
IfaceBuiltInSynFamTyCon |
Instances
data IfaceClassOp Source
Constructors
IfaceClassOp IfaceTopBndr DefMethSpec IfaceType |
Instances
data IfaceConDecl Source
Constructors
IfCon | |
Fields
|
Instances
data IfaceConDecls Source
Constructors
IfAbstractTyCon Bool | |
IfDataFamTyCon | |
IfDataTyCon [IfaceConDecl] | |
IfNewTyCon IfaceConDecl |
Instances
type IfaceEqSpec = [(IfLclName, IfaceType)] Source
Constructors
Instances
type IfaceAlt = (IfaceConAlt, [IfLclName], IfaceExpr) Source
data IfaceBinding Source
Constructors
IfaceNonRec IfaceLetBndr IfaceExpr | |
IfaceRec [(IfaceLetBndr, IfaceExpr)] |
Instances
data IfaceConAlt Source
Constructors
IfaceDefault | |
IfaceDataAlt IfExtName | |
IfaceLitAlt Literal |
Instances
data IfaceUnfolding Source
Constructors
IfCoreUnfold Bool IfaceExpr | |
IfCompulsory IfaceExpr | |
IfInlineRule Arity Bool Bool IfaceExpr | |
IfDFunUnfold [IfaceBndr] [IfaceExpr] |
Instances
data IfaceInfoItem Source
Constructors
HsArity Arity | |
HsStrictness StrictSig | |
HsInline InlinePragma | |
HsUnfold Bool IfaceUnfolding | |
HsNoCafRefs |
Instances
Constructors
IfaceRule | |
Fields
|
Instances
type IfaceAnnTarget = AnnTarget OccName Source
data IfaceClsInst Source
Constructors
IfaceClsInst | |
Fields
|
Instances
data IfaceTickish Source
Constructors
IfaceHpcTick Module Int | |
IfaceSCC CostCentre Bool Bool | |
IfaceSource RealSrcSpan String |
Instances
Constructors
IfNoBang | |
IfStrict | |
IfUnpack | |
IfUnpackCo IfaceCoercion |
data IfaceAxBranch Source
Constructors
IfaceAxBranch | |
Fields
|
Instances
data IfaceTyConParent Source
Constructors
IfNoParent | |
IfDataInstance IfExtName IfaceTyCon IfaceTcArgs |
Instances
ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName] Source
ifaceDeclFingerprints :: Fingerprint -> IfaceDecl -> [(OccName, Fingerprint)] Source
pprIfaceExpr :: (SDoc -> SDoc) -> IfaceExpr -> SDoc Source
Pretty Print an IfaceExpre
The first argument should be a function that adds parens in context that need an atomic value (e.g. function args)
pprIfaceDecl :: ShowSub -> IfaceDecl -> SDoc Source
Constructors
ShowSub | |
Fields
|
data ShowHowMuch Source
Constructors
ShowHeader | |
ShowSome [OccName] | |
ShowIface |