Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pretty-printing types and coercions.
Synopsis
- newtype PprPrec = PprPrec Int
- topPrec :: PprPrec
- sigPrec :: PprPrec
- opPrec :: PprPrec
- funPrec :: PprPrec
- appPrec :: PprPrec
- maybeParen :: PprPrec -> PprPrec -> SDoc -> SDoc
- pprType :: Type -> SDoc
- pprParendType :: Type -> SDoc
- pprTidiedType :: Type -> SDoc
- pprPrecType :: PprPrec -> Type -> SDoc
- pprPrecTypeX :: TidyEnv -> PprPrec -> Type -> SDoc
- pprTypeApp :: TyCon -> [Type] -> SDoc
- pprTCvBndr :: TyCoVarBinder -> SDoc
- pprTCvBndrs :: [TyCoVarBinder] -> SDoc
- pprSigmaType :: Type -> SDoc
- pprTheta :: ThetaType -> SDoc
- pprParendTheta :: ThetaType -> SDoc
- pprForAll :: [TyCoVarBinder] -> SDoc
- pprUserForAll :: [TyCoVarBinder] -> SDoc
- pprTyVar :: TyVar -> SDoc
- pprTyVars :: [TyVar] -> SDoc
- pprThetaArrowTy :: ThetaType -> SDoc
- pprClassPred :: Class -> [Type] -> SDoc
- pprKind :: Kind -> SDoc
- pprParendKind :: Kind -> SDoc
- pprTyLit :: TyLit -> SDoc
- pprDataCons :: TyCon -> SDoc
- pprWithExplicitKindsWhen :: Bool -> SDoc -> SDoc
- pprWithTYPE :: Type -> SDoc
- pprSourceTyCon :: TyCon -> SDoc
- pprCo :: Coercion -> SDoc
- pprParendCo :: Coercion -> SDoc
- debugPprType :: Type -> SDoc
- pprTyThingCategory :: TyThing -> SDoc
- pprShortTyThing :: TyThing -> SDoc
Precedence
A general-purpose pretty-printing precedence type.
Pretty-printing types
pprParendType :: Type -> SDoc Source #
pprTidiedType :: Type -> SDoc Source #
pprTCvBndr :: TyCoVarBinder -> SDoc Source #
pprTCvBndrs :: [TyCoVarBinder] -> SDoc Source #
pprSigmaType :: Type -> SDoc Source #
pprParendTheta :: ThetaType -> SDoc Source #
pprForAll :: [TyCoVarBinder] -> SDoc Source #
pprUserForAll :: [TyCoVarBinder] -> SDoc Source #
Print a user-level forall; see Note [When to print foralls]
in
GHC.Iface.Type.
pprThetaArrowTy :: ThetaType -> SDoc Source #
pprParendKind :: Kind -> SDoc Source #
pprDataCons :: TyCon -> SDoc Source #
pprWithExplicitKindsWhen :: Bool -> SDoc -> SDoc Source #
Display all kind information (with -fprint-explicit-kinds
) when the
provided Bool
argument is True
.
See Note [Kind arguments in error messages]
in GHC.Tc.Errors.
pprWithTYPE :: Type -> SDoc Source #
This variant preserves any use of TYPE in a type, effectively locally setting -fprint-explicit-runtime-reps.
pprSourceTyCon :: TyCon -> SDoc Source #
Pretty-printing coercions
pprParendCo :: Coercion -> SDoc Source #
debugPprType :: Type -> SDoc Source #
debugPprType is a simple pretty printer that prints a type without going through IfaceType. It does not format as prettily as the normal route, but it's much more direct, and that can be useful for debugging. E.g. with -dppr-debug it prints the kind on type-variable occurrences which the normal route fundamentally cannot do.
Pretty-printing TyThing
s
pprTyThingCategory :: TyThing -> SDoc Source #
pprShortTyThing :: TyThing -> SDoc Source #