Safe Haskell | None |
---|---|
Language | Haskell2010 |
IfaceSyn
Contents
- module IfaceType
- data IfaceDecl
- = IfaceId { }
- | IfaceData { }
- | IfaceSynonym {
- ifName :: IfaceTopBndr
- ifRoles :: [Role]
- ifBinders :: [IfaceTyConBinder]
- ifResKind :: IfaceKind
- ifSynRhs :: IfaceType
- | IfaceFamily { }
- | IfaceClass {
- ifName :: IfaceTopBndr
- ifRoles :: [Role]
- ifBinders :: [IfaceTyConBinder]
- ifFDs :: [FunDep IfLclName]
- ifBody :: IfaceClassBody
- | IfaceAxiom {
- ifName :: IfaceTopBndr
- ifTyCon :: IfaceTyCon
- ifRole :: Role
- ifAxBranches :: [IfaceAxBranch]
- | IfacePatSyn {
- ifName :: IfaceTopBndr
- ifPatIsInfix :: Bool
- ifPatMatcher :: (IfExtName, Bool)
- ifPatBuilder :: Maybe (IfExtName, Bool)
- ifPatUnivBndrs :: [IfaceForAllBndr]
- ifPatExBndrs :: [IfaceForAllBndr]
- ifPatProvCtxt :: IfaceContext
- ifPatReqCtxt :: IfaceContext
- ifPatArgs :: [IfaceType]
- ifPatTy :: IfaceType
- ifFieldLabels :: [FieldLabel]
- data IfaceFamTyConFlav
- data IfaceClassOp = IfaceClassOp IfaceTopBndr IfaceType (Maybe (DefMethSpec IfaceType))
- data IfaceAT = IfaceAT IfaceDecl (Maybe IfaceType)
- data IfaceConDecl = IfCon {}
- 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 IfaceJoinInfo
- data IfaceJoinInfo
- 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 IfaceClassBody
- = IfAbstractClass
- | IfConcreteClass {
- ifClassCtxt :: IfaceContext
- ifATs :: [IfaceAT]
- ifSigs :: [IfaceClassOp]
- ifMinDef :: BooleanFormula IfLclName
- data IfaceBang
- data IfaceSrcBang = IfSrcBang SrcUnpackedness SrcStrictness
- data SrcUnpackedness
- data SrcStrictness
- data IfaceAxBranch = IfaceAxBranch {
- ifaxbTyVars :: [IfaceTvBndr]
- ifaxbCoVars :: [IfaceIdBndr]
- ifaxbLHS :: IfaceTcArgs
- ifaxbRoles :: [Role]
- ifaxbRHS :: IfaceType
- ifaxbIncomps :: [BranchIndex]
- data IfaceTyConParent
- data IfaceCompleteMatch = IfaceCompleteMatch [IfExtName] IfExtName
- type IfaceTopBndr = Name
- putIfaceTopBndr :: BinHandle -> IfaceTopBndr -> IO ()
- getIfaceTopBndr :: BinHandle -> IO IfaceTopBndr
- 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
- newtype AltPpr = AltPpr (Maybe (OccName -> SDoc))
- data ShowSub = ShowSub {}
- data ShowHowMuch
- showToIface :: ShowSub
- showToHeader :: ShowSub
Documentation
module IfaceType
Constructors
data IfaceFamTyConFlav Source #
Constructors
IfaceDataFamilyTyCon | |
IfaceOpenSynFamilyTyCon | |
IfaceClosedSynFamilyTyCon (Maybe (IfExtName, [IfaceAxBranch])) | Name of associated axiom and branches for pretty printing purposes,
or |
IfaceAbstractClosedSynFamilyTyCon | |
IfaceBuiltInSynFamTyCon |
Instances
data IfaceClassOp Source #
Constructors
IfaceClassOp IfaceTopBndr IfaceType (Maybe (DefMethSpec IfaceType)) |
data IfaceConDecl Source #
Constructors
IfCon | |
Fields
|
Instances
data IfaceConDecls Source #
Constructors
IfAbstractTyCon | |
IfDataTyCon [IfaceConDecl] | |
IfNewTyCon IfaceConDecl |
Instances
type IfaceEqSpec = [(IfLclName, IfaceType)] Source #
Constructors
data IfaceLetBndr Source #
Constructors
IfLetBndr IfLclName IfaceType IfaceIdInfo IfaceJoinInfo |
Instances
data IfaceBinding Source #
Constructors
IfaceNonRec IfaceLetBndr IfaceExpr | |
IfaceRec [(IfaceLetBndr, IfaceExpr)] |
Instances
data IfaceConAlt Source #
Constructors
IfaceDefault | |
IfaceDataAlt IfExtName | |
IfaceLitAlt Literal |
Instances
data IfaceIdDetails Source #
Constructors
IfVanillaId | |
IfRecSelId (Either IfaceTyCon IfaceDecl) Bool | |
IfDFunId |
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 | |
HsLevity |
Instances
Constructors
IfaceRule | |
Fields
|
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
data IfaceClassBody Source #
Constructors
IfAbstractClass | |
IfConcreteClass | |
Fields
|
This corresponds to an HsImplBang; that is, the final implementation decision about the data constructor arg
Constructors
IfNoBang | |
IfStrict | |
IfUnpack | |
IfUnpackCo IfaceCoercion |
data IfaceSrcBang Source #
This corresponds to HsSrcBang
Constructors
IfSrcBang SrcUnpackedness SrcStrictness |
Instances
data SrcUnpackedness Source #
Source Unpackedness
What unpackedness the user requested
Constructors
SrcUnpack | |
SrcNoUnpack | |
NoSrcUnpack | no unpack pragma |
data SrcStrictness Source #
Source Strictness
What strictness annotation the user wrote
Constructors
SrcLazy | Lazy, ie '~' |
SrcStrict | Strict, ie |
NoSrcStrict | no strictness annotation |
data IfaceAxBranch Source #
Constructors
IfaceAxBranch | |
Fields
|
Instances
data IfaceTyConParent Source #
Constructors
IfNoParent | |
IfDataInstance IfExtName IfaceTyCon IfaceTcArgs |
Instances
Binding names
type IfaceTopBndr = Name Source #
putIfaceTopBndr :: BinHandle -> IfaceTopBndr -> IO () Source #
ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName] Source #
ifaceDeclFingerprints :: Fingerprint -> IfaceDecl -> [(OccName, Fingerprint)] Source #
freeNamesIfDecl :: IfaceDecl -> NameSet Source #
freeNamesIfRule :: IfaceRule -> NameSet 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)
Constructors
ShowSub | |
Fields |
data ShowHowMuch Source #
Constructors
ShowHeader AltPpr | Header information only, not rhs |
ShowSome [OccName] AltPpr | Show only some sub-components. Specifically,
|
ShowIface | Everything including GHC-internal information (used in --show-iface) |
Instances