ghc-6.10.3: The GHC APIContentsIndex
IfaceType
Documentation
data IfaceType
Constructors
IfaceTyVar FastString
IfaceAppTy IfaceType IfaceType
IfaceForAllTy IfaceTvBndr IfaceType
IfacePredTy IfacePredType
IfaceTyConApp IfaceTyCon [IfaceType]
IfaceFunTy IfaceType IfaceType
show/hide Instances
type IfaceKind = IfaceType
data IfacePredType
Constructors
IfaceClassP Name [IfaceType]
IfaceIParam (IPName OccName) IfaceType
IfaceEqPred IfaceType IfaceType
show/hide Instances
data IfaceTyCon
Constructors
IfaceTc Name
IfaceIntTc
IfaceBoolTc
IfaceCharTc
IfaceListTc
IfacePArrTc
IfaceTupTc Boxity Arity
IfaceLiftedTypeKindTc
IfaceOpenTypeKindTc
IfaceUnliftedTypeKindTc
IfaceUbxTupleKindTc
IfaceArgTypeKindTc
show/hide Instances
type IfaceContext = [IfacePredType]
data IfaceBndr
Constructors
IfaceIdBndr !IfaceIdBndr
IfaceTvBndr !IfaceTvBndr
show/hide Instances
type IfaceTvBndr = (FastString, IfaceKind)
type IfaceIdBndr = (FastString, IfaceType)
type IfaceCoercion = IfaceType
ifaceTyConName :: IfaceTyCon -> Name
toIfaceType :: Type -> IfaceType
toIfacePred :: PredType -> IfacePredType
toIfaceContext :: ThetaType -> IfaceContext
toIfaceBndr :: Var -> IfaceBndr
toIfaceIdBndr :: Id -> (FastString, IfaceType)
toIfaceTvBndrs :: [TyVar] -> [(FastString, IfaceType)]
toIfaceTyCon :: TyCon -> IfaceTyCon
toIfaceTyCon_name :: Name -> IfaceTyCon
pprIfaceType :: IfaceType -> SDoc
pprParendIfaceType :: IfaceType -> SDoc
pprIfaceContext :: IfaceContext -> SDoc
pprIfaceIdBndr :: (FastString, IfaceType) -> SDoc
pprIfaceTvBndr :: IfaceTvBndr -> SDoc
pprIfaceTvBndrs :: [IfaceTvBndr] -> SDoc
pprIfaceBndrs :: [IfaceBndr] -> SDoc
tOP_PREC :: Int
tYCON_PREC :: Int
noParens :: SDoc -> SDoc
maybeParen :: Int -> Int -> SDoc -> SDoc
pprIfaceForAllPart :: [IfaceTvBndr] -> IfaceContext -> SDoc -> SDoc
Produced by Haddock version 2.4.2