Safe Haskell | None |
---|---|
Language | Haskell2010 |
- module IfaceType
- data IfaceDecl
- = IfaceId {
- ifName :: IfaceTopBndr
- ifType :: IfaceType
- ifIdDetails :: IfaceIdDetails
- ifIdInfo :: IfaceIdInfo
- | IfaceData {
- ifName :: IfaceTopBndr
- ifBinders :: [IfaceTyConBinder]
- ifResKind :: IfaceType
- ifCType :: Maybe CType
- ifRoles :: [Role]
- ifCtxt :: IfaceContext
- ifCons :: IfaceConDecls
- ifRec :: RecFlag
- ifGadtSyntax :: Bool
- ifParent :: IfaceTyConParent
- | IfaceSynonym { }
- | IfaceFamily {
- ifName :: IfaceTopBndr
- ifResVar :: Maybe IfLclName
- ifBinders :: [IfaceTyConBinder]
- ifResKind :: IfaceKind
- ifFamFlav :: IfaceFamTyConFlav
- ifFamInj :: Injectivity
- | IfaceClass {
- ifCtxt :: IfaceContext
- ifName :: IfaceTopBndr
- ifRoles :: [Role]
- ifBinders :: [IfaceTyConBinder]
- 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)
- ifPatUnivBndrs :: [IfaceForAllBndr]
- ifPatExBndrs :: [IfaceForAllBndr]
- ifPatProvCtxt :: IfaceContext
- ifPatReqCtxt :: IfaceContext
- ifPatArgs :: [IfaceType]
- ifPatTy :: IfaceType
- ifFieldLabels :: [FieldLabel]
- = IfaceId {
- data IfaceFamTyConFlav
- data IfaceClassOp = IfaceClassOp IfaceTopBndr IfaceType (Maybe (DefMethSpec IfaceType))
- data IfaceAT = IfaceAT IfaceDecl (Maybe IfaceType)
- data IfaceConDecl = IfCon {
- ifConOcc :: IfaceTopBndr
- ifConWrapper :: Bool
- ifConInfix :: Bool
- ifConExTvs :: [IfaceForAllBndr]
- ifConEqSpec :: IfaceEqSpec
- ifConCtxt :: IfaceContext
- ifConArgTys :: [IfaceType]
- ifConFields :: [IfaceTopBndr]
- ifConStricts :: [IfaceBang]
- ifConSrcStricts :: [IfaceSrcBang]
- 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 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
- ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName]
- visibleIfConDecls :: IfaceConDecls -> [IfaceConDecl]
- ifaceConDeclFields :: IfaceConDecls -> [FieldLbl OccName]
- 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
data IfaceFamTyConFlav Source #
IfaceDataFamilyTyCon | |
IfaceOpenSynFamilyTyCon | |
IfaceClosedSynFamilyTyCon (Maybe (IfExtName, [IfaceAxBranch])) | Name of associated axiom and branches for pretty printing purposes,
or |
IfaceAbstractClosedSynFamilyTyCon | |
IfaceBuiltInSynFamTyCon |
data IfaceClassOp Source #
IfaceClassOp IfaceTopBndr IfaceType (Maybe (DefMethSpec IfaceType)) |
data IfaceConDecl Source #
IfCon | |
|
data IfaceConDecls Source #
type IfaceEqSpec = [(IfLclName, IfaceType)] Source #
data IfaceBinding Source #
data IfaceConAlt Source #
data IfaceIdInfo Source #
data IfaceIdDetails Source #
data IfaceUnfolding Source #
data IfaceInfoItem Source #
IfaceRule | |
|
data IfaceAnnotation Source #
type IfaceAnnTarget = AnnTarget OccName Source #
data IfaceClsInst Source #
IfaceClsInst | |
|
data IfaceTickish Source #
This corresponds to an HsImplBang; that is, the final implementation decision about the data constructor arg
data IfaceSrcBang Source #
This corresponds to HsSrcBang
data SrcUnpackedness Source #
What unpackedness the user requested
SrcUnpack | |
SrcNoUnpack | |
NoSrcUnpack | no unpack pragma |
data SrcStrictness Source #
What strictness annotation the user wrote
SrcLazy | Lazy, ie '~' |
SrcStrict | Strict, ie |
NoSrcStrict | no strictness annotation |
data IfaceAxBranch Source #
IfaceAxBranch | |
|
data IfaceTyConParent 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)
ShowSub | |
|