ghc-lib-parser-9.4.3.20221104: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Utils.Outputable

Description

This module defines classes and functions for pretty-printing. It also exports a number of helpful debugging and other utilities such as trace and panic.

The interface to this module is very similar to the standard Hughes-PJ pretty printing module, except that it exports a number of additional functions that are rarely used, and works over the SDoc type.

Synopsis

Type classes

class Outputable a where Source #

Class designating that some type has an SDoc representation

Methods

ppr :: a -> SDoc Source #

Instances

Instances details
Outputable Fingerprint Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Fingerprint -> SDoc Source #

Outputable Int32 Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int32 -> SDoc Source #

Outputable Int64 Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int64 -> SDoc Source #

Outputable Word16 Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word16 -> SDoc Source #

Outputable Word32 Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word32 -> SDoc Source #

Outputable Word64 Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word64 -> SDoc Source #

Outputable IntSet Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: IntSet -> SDoc Source #

Outputable PrimCall Source # 
Instance details

Defined in GHC.Builtin.PrimOps

Methods

ppr :: PrimCall -> SDoc Source #

Outputable PrimOp Source # 
Instance details

Defined in GHC.Builtin.PrimOps

Methods

ppr :: PrimOp -> SDoc Source #

Outputable ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: ByteOff -> SDoc Source #

Outputable CgBreakInfo Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: CgBreakInfo -> SDoc Source #

Outputable CompiledByteCode Source # 
Instance details

Defined in GHC.ByteCode.Types

Outputable RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: RegBitmap -> SDoc Source #

Outputable TupleInfo Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: TupleInfo -> SDoc Source #

Outputable UnlinkedBCO Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: UnlinkedBCO -> SDoc Source #

Outputable WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: WordOff -> SDoc Source #

Outputable CmmStatic Source # 
Instance details

Defined in GHC.Cmm

Methods

ppr :: CmmStatic -> SDoc Source #

Outputable CLabel Source # 
Instance details

Defined in GHC.Cmm.CLabel

Methods

ppr :: CLabel -> SDoc Source #

Outputable ConInfoTableLocation Source # 
Instance details

Defined in GHC.Cmm.CLabel

Outputable ForeignLabelSource Source # 
Instance details

Defined in GHC.Cmm.CLabel

Outputable Label Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: Label -> SDoc Source #

Outputable LabelSet Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: LabelSet -> SDoc Source #

Outputable CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

ppr :: CmmLit -> SDoc Source #

Outputable CmmTickScope Source # 
Instance details

Defined in GHC.Cmm.Node

Outputable CmmType Source # 
Instance details

Defined in GHC.Cmm.Type

Methods

ppr :: CmmType -> SDoc Source #

Outputable Width Source # 
Instance details

Defined in GHC.Cmm.Type

Methods

ppr :: Width -> SDoc Source #

Outputable AltCon Source # 
Instance details

Defined in GHC.Core

Methods

ppr :: AltCon -> SDoc Source #

Outputable CoreRule Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: CoreRule -> SDoc Source #

Outputable Unfolding Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: Unfolding -> SDoc Source #

Outputable UnfoldingGuidance Source # 
Instance details

Defined in GHC.Core.Ppr

Outputable UnfoldingSource Source # 
Instance details

Defined in GHC.Core.Ppr

Outputable Class Source # 
Instance details

Defined in GHC.Core.Class

Methods

ppr :: Class -> SDoc Source #

Outputable LiftingContext Source # 
Instance details

Defined in GHC.Core.Coercion

Outputable CoAxBranch Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxBranch -> SDoc Source #

Outputable CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiomRule -> SDoc Source #

Outputable Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: Role -> SDoc Source #

Outputable ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Methods

ppr :: ConLike -> SDoc Source #

Outputable DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: DataCon -> SDoc Source #

Outputable EqSpec Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: EqSpec -> SDoc Source #

Outputable HsImplBang Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsImplBang -> SDoc Source #

Outputable HsSrcBang Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsSrcBang -> SDoc Source #

Outputable SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable StrictnessMark Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable FamInst Source # 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInst -> SDoc Source #

Outputable FamInstEnv Source # 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInstEnv -> SDoc Source #

Outputable FamInstMatch Source # 
Instance details

Defined in GHC.Core.FamInstEnv

Outputable ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: ClsInst -> SDoc Source #

Outputable InstEnv Source # 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: InstEnv -> SDoc Source #

Outputable PotentialUnifiers Source # 
Instance details

Defined in GHC.Core.InstEnv

Outputable FloatBind Source # 
Instance details

Defined in GHC.Core.Make

Methods

ppr :: FloatBind -> SDoc Source #

Outputable IsSubmult Source # 
Instance details

Defined in GHC.Core.Multiplicity

Methods

ppr :: IsSubmult -> SDoc Source #

Outputable ArityType Source #

This is the BNF of the generated output:

@

We format

AT [o1,..,on] topDiv as o1..on.T and AT [o1,..,on] botDiv as o1..on.⊥, respectively. More concretely, AT [NOI,OS,OS] topDiv is formatted as ?11.T. If the one-shot info is empty, we omit the leading .@.

Instance details

Defined in GHC.Core.Opt.Arity

Methods

ppr :: ArityType -> SDoc Source #

Outputable CallerCcFilter Source # 
Instance details

Defined in GHC.Core.Opt.CallerCC

Outputable NamePattern Source # 
Instance details

Defined in GHC.Core.Opt.CallerCC

Methods

ppr :: NamePattern -> SDoc Source #

Outputable CoreToDo Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: CoreToDo -> SDoc Source #

Outputable FloatOutSwitches Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Outputable SimplMode Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: SimplMode -> SDoc Source #

Outputable Tick Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: Tick -> SDoc Source #

Outputable PatSyn Source # 
Instance details

Defined in GHC.Core.PatSyn

Methods

ppr :: PatSyn -> SDoc Source #

Outputable EqRel Source # 
Instance details

Defined in GHC.Core.Predicate

Methods

ppr :: EqRel -> SDoc Source #

Outputable Reduction Source # 
Instance details

Defined in GHC.Core.Reduction

Methods

ppr :: Reduction -> SDoc Source #

Outputable RoughMatchLookupTc Source # 
Instance details

Defined in GHC.Core.RoughMap

Outputable RoughMatchTc Source # 
Instance details

Defined in GHC.Core.RoughMap

Outputable CoreStats Source # 
Instance details

Defined in GHC.Core.Stats

Methods

ppr :: CoreStats -> SDoc Source #

Outputable Subst Source # 
Instance details

Defined in GHC.Core.Subst

Methods

ppr :: Subst -> SDoc Source #

Outputable Coercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Coercion -> SDoc Source #

Outputable CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable MCoercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: MCoercion -> SDoc Source #

Outputable TyCoBinder Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyCoBinder -> SDoc Source #

Outputable TyLit Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyLit -> SDoc Source #

Outputable Type Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc Source #

Outputable UnivCoProvenance Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable TCvSubst Source # 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: TCvSubst -> SDoc Source #

Outputable AlgTyConFlav Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable FamTyConFlav Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable PrimElemRep Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: PrimElemRep -> SDoc Source #

Outputable PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: PrimRep -> SDoc Source #

Outputable TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyCon -> SDoc Source #

Outputable TyConBndrVis Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable TyConFlavour Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable RecTcChecker Source # 
Instance details

Defined in GHC.Core.TyCon.RecWalk

Outputable ArgSummary Source # 
Instance details

Defined in GHC.Core.Unfold

Methods

ppr :: ArgSummary -> SDoc Source #

Outputable CallCtxt Source # 
Instance details

Defined in GHC.Core.Unfold

Methods

ppr :: CallCtxt -> SDoc Source #

Outputable MaybeApartReason Source # 
Instance details

Defined in GHC.Core.Unify

Outputable Usage Source # 
Instance details

Defined in GHC.Core.UsageEnv

Methods

ppr :: Usage -> SDoc Source #

Outputable UsageEnv Source # 
Instance details

Defined in GHC.Core.UsageEnv

Methods

ppr :: UsageEnv -> SDoc Source #

Outputable FastString Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: FastString -> SDoc Source #

Outputable LexicalFastString Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable NonDetFastString Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable EdgeType Source # 
Instance details

Defined in GHC.Data.Graph.Directed

Methods

ppr :: EdgeType -> SDoc Source #

Outputable UnVarGraph Source # 
Instance details

Defined in GHC.Data.Graph.UnVar

Methods

ppr :: UnVarGraph -> SDoc Source #

Outputable UnVarSet Source # 
Instance details

Defined in GHC.Data.Graph.UnVar

Methods

ppr :: UnVarSet -> SDoc Source #

Outputable HsComponentId Source # 
Instance details

Defined in GHC.Driver.Backpack.Syntax

Outputable WarnReason Source # 
Instance details

Defined in GHC.Driver.CmdLine

Methods

ppr :: WarnReason -> SDoc Source #

Outputable Language Source # 
Instance details

Defined in GHC.Driver.Flags

Methods

ppr :: Language -> SDoc Source #

Outputable Phase Source # 
Instance details

Defined in GHC.Driver.Phases

Methods

ppr :: Phase -> SDoc Source #

Outputable PluginRecompile Source # 
Instance details

Defined in GHC.Driver.Plugins

Outputable GhcMode Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: GhcMode -> SDoc Source #

Outputable ModRenaming Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: ModRenaming -> SDoc Source #

Outputable PackageArg Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageArg -> SDoc Source #

Outputable PackageFlag Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageFlag -> SDoc Source #

Outputable HsModule Source # 
Instance details

Defined in GHC.Hs

Methods

ppr :: HsModule -> SDoc Source #

Outputable ABExport Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: ABExport -> SDoc Source #

Outputable TcSpecPrag Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: TcSpecPrag -> SDoc Source #

Outputable XViaStrategyPs Source # 
Instance details

Defined in GHC.Hs.Decls

Outputable DocStructureItem Source # 
Instance details

Defined in GHC.Hs.Doc

Outputable Docs Source # 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: Docs -> SDoc Source #

Outputable HsDocString Source # 
Instance details

Defined in GHC.Hs.DocString

Methods

ppr :: HsDocString -> SDoc Source #

Outputable HsDocStringChunk Source # 
Instance details

Defined in GHC.Hs.DocString

Outputable HsDocStringDecorator Source # 
Instance details

Defined in GHC.Hs.DocString

Outputable GrhsAnn Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: GrhsAnn -> SDoc Source #

Outputable PendingRnSplice Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable PendingTcSplice Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable SyntaxExprRn Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable SyntaxExprTc Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable XXExprGhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: XXExprGhcTc -> SDoc Source #

Outputable BotInfo Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: BotInfo -> SDoc Source #

Outputable Nabla Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: Nabla -> SDoc Source #

Outputable Nablas Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: Nablas -> SDoc Source #

Outputable PmAltCon Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltCon -> SDoc Source #

Outputable PmAltConApp Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltConApp -> SDoc Source #

Outputable PmAltConSet Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltConSet -> SDoc Source #

Outputable PmEquality Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmEquality -> SDoc Source #

Outputable PmLit Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmLit -> SDoc Source #

Outputable PmLitValue Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmLitValue -> SDoc Source #

Outputable ResidualCompleteMatches Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Outputable TmState Source #

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: TmState -> SDoc Source #

Outputable TyState Source #

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: TyState -> SDoc Source #

Outputable VarInfo Source #

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: VarInfo -> SDoc Source #

Outputable GrdVec Source #

Format LYG guards as | True <- x, let x = 42, !z

Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: GrdVec -> SDoc Source #

Outputable PmEmptyCase Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmEmptyCase -> SDoc Source #

Outputable PmGrd Source #

Should not be user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGrd -> SDoc Source #

Outputable Precision Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: Precision -> SDoc Source #

Outputable RedSets Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: RedSets -> SDoc Source #

Outputable SrcInfo Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: SrcInfo -> SDoc Source #

Outputable IfaceAT Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceAT -> SDoc Source #

Outputable IfaceAnnotation Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceClsInst Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceCompleteMatch Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceConAlt Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceConAlt -> SDoc Source #

Outputable IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceDecl -> SDoc Source #

Outputable IfaceExpr Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceExpr -> SDoc Source #

Outputable IfaceFamInst Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceIdDetails Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceInfoItem Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceJoinInfo Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceLFInfo Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceLFInfo -> SDoc Source #

Outputable IfaceRule Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceRule -> SDoc Source #

Outputable IfaceTyConParent Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceUnfolding Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable ShowHowMuch Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: ShowHowMuch -> SDoc Source #

Outputable IfaceAppArgs Source # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceBndr Source # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceBndr -> SDoc Source #

Outputable IfaceCoercion Source # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceOneShot Source # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyCon Source # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceTyCon -> SDoc Source #

Outputable IfaceTyConInfo Source # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyConSort Source # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyLit Source # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceTyLit -> SDoc Source #

Outputable IfaceType Source # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceType -> SDoc Source #

Outputable Extension Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Extension -> SDoc Source #

Outputable LibrarySpec Source # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: LibrarySpec -> SDoc Source #

Outputable Linkable Source # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Linkable -> SDoc Source #

Outputable LoadedPkgInfo Source # 
Instance details

Defined in GHC.Linker.Types

Outputable SptEntry Source # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: SptEntry -> SDoc Source #

Outputable Unlinked Source # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Unlinked -> SDoc Source #

Outputable AddEpAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AddEpAnn -> SDoc Source #

Outputable Anchor Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: Anchor -> SDoc Source #

Outputable AnchorOperation Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnContext Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnContext -> SDoc Source #

Outputable AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnList Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnList -> SDoc Source #

Outputable AnnListItem Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnListItem -> SDoc Source #

Outputable AnnPragma Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnPragma -> SDoc Source #

Outputable AnnSortKey Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnSortKey -> SDoc Source #

Outputable DeltaPos Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: DeltaPos -> SDoc Source #

Outputable EpAnnComments Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaComment -> SDoc Source #

Outputable EpaLocation Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaLocation -> SDoc Source #

Outputable IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable NameAdornment Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable NameAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NameAnn -> SDoc Source #

Outputable NoEpAnns Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NoEpAnns -> SDoc Source #

Outputable TrailingAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: TrailingAnn -> SDoc Source #

Outputable Token Source # 
Instance details

Defined in GHC.Parser.Lexer

Methods

ppr :: Token -> SDoc Source #

Outputable DataConBuilder Source # 
Instance details

Defined in GHC.Parser.Types

Outputable RealReg Source # 
Instance details

Defined in GHC.Platform.Reg

Methods

ppr :: RealReg -> SDoc Source #

Outputable Reg Source #

Print a reg in a generic manner If you want the architecture specific names, then use the pprReg function from the appropriate Ppr module.

Instance details

Defined in GHC.Platform.Reg

Methods

ppr :: Reg -> SDoc Source #

Outputable VirtualReg Source # 
Instance details

Defined in GHC.Platform.Reg

Methods

ppr :: VirtualReg -> SDoc Source #

Outputable RegClass Source # 
Instance details

Defined in GHC.Platform.Reg.Class

Methods

ppr :: RegClass -> SDoc Source #

Outputable InteractiveImport Source # 
Instance details

Defined in GHC.Runtime.Context

Outputable ArgDescr Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Methods

ppr :: ArgDescr -> SDoc Source #

Outputable ClosureTypeInfo Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Outputable SMRep Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Methods

ppr :: SMRep -> SDoc Source #

Outputable StgHalfWord Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Methods

ppr :: StgHalfWord -> SDoc Source #

Outputable StgWord Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Methods

ppr :: StgWord -> SDoc Source #

Outputable Serialized Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Serialized -> SDoc Source #

Outputable TagInfo Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

Methods

ppr :: TagInfo -> SDoc Source #

Outputable TagSig Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

Methods

ppr :: TagSig -> SDoc Source #

Outputable AltType Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: AltType -> SDoc Source #

Outputable ConstructorNumber Source # 
Instance details

Defined in GHC.Stg.Syntax

Outputable NoExtFieldSilent Source # 
Instance details

Defined in GHC.Stg.Syntax

Outputable StgArg Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: StgArg -> SDoc Source #

Outputable StgOp Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: StgOp -> SDoc Source #

Outputable UpdateFlag Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: UpdateFlag -> SDoc Source #

Outputable LambdaFormInfo Source # 
Instance details

Defined in GHC.StgToCmm.Types

Outputable StandardFormInfo Source # 
Instance details

Defined in GHC.StgToCmm.Types

Outputable HoleFit Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

ppr :: HoleFit -> SDoc Source #

Outputable HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Outputable TypedHole Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

ppr :: TypedHole -> SDoc Source #

Outputable ErrorItem Source # 
Instance details

Defined in GHC.Tc.Errors.Types

Methods

ppr :: ErrorItem -> SDoc Source #

Outputable Exported Source # 
Instance details

Defined in GHC.Tc.Errors.Types

Methods

ppr :: Exported -> SDoc Source #

Outputable ImportError Source # 
Instance details

Defined in GHC.Tc.Errors.Ppr

Methods

ppr :: ImportError -> SDoc Source #

Outputable SolverReportErrCtxt Source # 
Instance details

Defined in GHC.Tc.Errors.Ppr

Outputable InertCans Source # 
Instance details

Defined in GHC.Tc.Solver.InertSet

Methods

ppr :: InertCans -> SDoc Source #

Outputable InertSet Source # 
Instance details

Defined in GHC.Tc.Solver.InertSet

Methods

ppr :: InertSet -> SDoc Source #

Outputable WorkList Source # 
Instance details

Defined in GHC.Tc.Solver.InertSet

Methods

ppr :: WorkList -> SDoc Source #

Outputable DefaultingProposal Source # 
Instance details

Defined in GHC.Tc.Types

Outputable IdBindingInfo Source # 
Instance details

Defined in GHC.Tc.Types

Outputable PromotionErr Source # 
Instance details

Defined in GHC.Tc.Types

Outputable TcBinder Source # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcBinder -> SDoc Source #

Outputable TcIdSigInfo Source # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInfo -> SDoc Source #

Outputable TcIdSigInst Source # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInst -> SDoc Source #

Outputable TcPatSynInfo Source # 
Instance details

Defined in GHC.Tc.Types

Outputable TcSigInfo Source # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcSigInfo -> SDoc Source #

Outputable TcTyThing Source # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcTyThing -> SDoc Source #

Outputable ThStage Source # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: ThStage -> SDoc Source #

Outputable WhereFrom Source # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: WhereFrom -> SDoc Source #

Outputable CanEqLHS Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CanEqLHS -> SDoc Source #

Outputable CheckTyEqResult Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable Ct Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Ct -> SDoc Source #

Outputable CtEvidence Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CtEvidence -> SDoc Source #

Outputable CtFlavour Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CtFlavour -> SDoc Source #

Outputable CtIrredReason Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable DelayedError Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable HasGivenEqs Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: HasGivenEqs -> SDoc Source #

Outputable Hole Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Hole -> SDoc Source #

Outputable HoleSort Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: HoleSort -> SDoc Source #

Outputable ImplicStatus Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable Implication Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Implication -> SDoc Source #

Outputable NotConcreteError Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable QCInst Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: QCInst -> SDoc Source #

Outputable RewriterSet Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: RewriterSet -> SDoc Source #

Outputable SubGoalDepth Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable TcEvDest Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: TcEvDest -> SDoc Source #

Outputable WantedConstraints Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable EvBind Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBind -> SDoc Source #

Outputable EvBindMap Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindMap -> SDoc Source #

Outputable EvBindsVar Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindsVar -> SDoc Source #

Outputable EvCallStack Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvCallStack -> SDoc Source #

Outputable EvTerm Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTerm -> SDoc Source #

Outputable EvTypeable Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTypeable -> SDoc Source #

Outputable HoleExprRef Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HoleExprRef -> SDoc Source #

Outputable HsWrapper Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HsWrapper -> SDoc Source #

Outputable TcEvBinds Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: TcEvBinds -> SDoc Source #

Outputable CtOrigin Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: CtOrigin -> SDoc Source #

Outputable FRRArrowContext Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Outputable FixedRuntimeRepContext Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Outputable SkolemInfo Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: SkolemInfo -> SDoc Source #

Outputable SkolemInfoAnon Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Outputable StmtOrigin Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: StmtOrigin -> SDoc Source #

Outputable TyVarBndrs Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: TyVarBndrs -> SDoc Source #

Outputable TypedThing Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: TypedThing -> SDoc Source #

Outputable Rank Source # 
Instance details

Defined in GHC.Tc.Types.Rank

Methods

ppr :: Rank -> SDoc Source #

Outputable ExpType Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: ExpType -> SDoc Source #

Outputable InferResult Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: InferResult -> SDoc Source #

Outputable MetaDetails Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: MetaDetails -> SDoc Source #

Outputable MetaInfo Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: MetaInfo -> SDoc Source #

Outputable TcLevel Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: TcLevel -> SDoc Source #

Outputable TcTyVarDetails Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable Annotation Source # 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: Annotation -> SDoc Source #

Outputable AvailInfo Source # 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: AvailInfo -> SDoc Source #

Outputable GreName Source # 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: GreName -> SDoc Source #

Outputable Activation Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Activation -> SDoc Source #

Outputable Alignment Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Alignment -> SDoc Source #

Outputable Boxity Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Boxity -> SDoc Source #

Outputable CbvMark Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: CbvMark -> SDoc Source #

Outputable CompilerPhase Source # 
Instance details

Defined in GHC.Types.Basic

Outputable DefaultingStrategy Source # 
Instance details

Defined in GHC.Types.Basic

Outputable ExprOrPat Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: ExprOrPat -> SDoc Source #

Outputable FunctionOrData Source # 
Instance details

Defined in GHC.Types.Basic

Outputable InlinePragma Source # 
Instance details

Defined in GHC.Types.Basic

Outputable InlineSpec Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: InlineSpec -> SDoc Source #

Outputable IntWithInf Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: IntWithInf -> SDoc Source #

Outputable LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc Source #

Outputable Levity Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Levity -> SDoc Source #

Outputable NonStandardDefaultingStrategy Source # 
Instance details

Defined in GHC.Types.Basic

Outputable OccInfo Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OccInfo -> SDoc Source #

Outputable OneShotInfo Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OneShotInfo -> SDoc Source #

Outputable Origin Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Origin -> SDoc Source #

Outputable OverlapFlag Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapFlag -> SDoc Source #

Outputable OverlapMode Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapMode -> SDoc Source #

Outputable PromotionFlag Source # 
Instance details

Defined in GHC.Types.Basic

Outputable RecFlag Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: RecFlag -> SDoc Source #

Outputable RuleMatchInfo Source # 
Instance details

Defined in GHC.Types.Basic

Outputable SuccessFlag Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SuccessFlag -> SDoc Source #

Outputable SwapFlag Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SwapFlag -> SDoc Source #

Outputable TailCallInfo Source # 
Instance details

Defined in GHC.Types.Basic

Outputable TopLevelFlag Source # 
Instance details

Defined in GHC.Types.Basic

Outputable TupleSort Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TupleSort -> SDoc Source #

Outputable TypeOrKind Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TypeOrKind -> SDoc Source #

Outputable UnboxedTupleOrSum Source # 
Instance details

Defined in GHC.Types.Basic

Outputable CompleteMatch Source # 
Instance details

Defined in GHC.Types.CompleteMatch

Outputable CostCentre Source # 
Instance details

Defined in GHC.Types.CostCentre

Methods

ppr :: CostCentre -> SDoc Source #

Outputable CostCentreStack Source # 
Instance details

Defined in GHC.Types.CostCentre

Outputable Cpr Source #

BNF:

cpr ::= ''                               -- TopCpr
     |  n                                -- FlatConCpr n
     |  n '(' cpr1 ',' cpr2 ',' ... ')'  -- ConCpr n [cpr1,cpr2,...]
     |  'b'                              -- BotCpr

Examples: * `f x = f x` has result CPR b * `1(1,)` is a valid (nested) Cpr denotation for `(I# 42#, f 42)`.

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: Cpr -> SDoc Source #

Outputable CprSig Source #

Only print the CPR result

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprSig -> SDoc Source #

Outputable CprType Source #

BNF:

cpr_ty ::= cpr               -- short form if arty == 0
        |  '\' arty '.' cpr  -- if arty > 0

Examples: * `f x y z = f x y z` has denotation `3.b` * `g !x = (x+1, x+2)` has denotation `1.1(1,1)`.

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprType -> SDoc Source #

Outputable Card Source #

See Note [Demand notation] Current syntax was discussed in #19016.

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Card -> SDoc Source #

Outputable Demand Source #

See Note [Demand notation]

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Demand -> SDoc Source #

Outputable Divergence Source # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Divergence -> SDoc Source #

Outputable DmdSig Source # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: DmdSig -> SDoc Source #

Outputable DmdType Source # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: DmdType -> SDoc Source #

Outputable SubDemand Source #

See Note [Demand notation]

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: SubDemand -> SDoc Source #

Outputable TypeShape Source # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: TypeShape -> SDoc Source #

Outputable DiagnosticHint Source # 
Instance details

Defined in GHC.Types.Error

Outputable DiagnosticReason Source # 
Instance details

Defined in GHC.Types.Error

Outputable Severity Source # 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Severity -> SDoc Source #

Outputable DuplicateRecordFields Source # 
Instance details

Defined in GHC.Types.FieldLabel

Outputable FieldLabel Source # 
Instance details

Defined in GHC.Types.FieldLabel

Methods

ppr :: FieldLabel -> SDoc Source #

Outputable FieldSelectors Source # 
Instance details

Defined in GHC.Types.FieldLabel

Outputable Fixity Source # 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: Fixity -> SDoc Source #

Outputable FixityDirection Source # 
Instance details

Defined in GHC.Types.Fixity

Outputable LexicalFixity Source # 
Instance details

Defined in GHC.Types.Fixity

Outputable FixItem Source # 
Instance details

Defined in GHC.Types.Fixity.Env

Methods

ppr :: FixItem -> SDoc Source #

Outputable CCallConv Source # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CCallConv -> SDoc Source #

Outputable CCallSpec Source # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CCallSpec -> SDoc Source #

Outputable CExportSpec Source # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CExportSpec -> SDoc Source #

Outputable CType Source # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CType -> SDoc Source #

Outputable ForeignCall Source # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: ForeignCall -> SDoc Source #

Outputable Header Source # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: Header -> SDoc Source #

Outputable Safety Source # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: Safety -> SDoc Source #

Outputable GhcHint Source # 
Instance details

Defined in GHC.Types.Hint.Ppr

Methods

ppr :: GhcHint -> SDoc Source #

Outputable CafInfo Source # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: CafInfo -> SDoc Source #

Outputable IdDetails Source # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: IdDetails -> SDoc Source #

Outputable IdInfo Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: IdInfo -> SDoc Source #

Outputable LevityInfo Source # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: LevityInfo -> SDoc Source #

Outputable RecSelParent Source # 
Instance details

Defined in GHC.Types.Id.Info

Outputable TickBoxOp Source # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: TickBoxOp -> SDoc Source #

Outputable Literal Source # 
Instance details

Defined in GHC.Types.Literal

Methods

ppr :: Literal -> SDoc Source #

Outputable Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc Source #

Outputable OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc Source #

Outputable GlobalRdrElt Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable ImportSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: ImportSpec -> SDoc Source #

Outputable LocalRdrEnv Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: LocalRdrEnv -> SDoc Source #

Outputable Parent Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: Parent -> SDoc Source #

Outputable RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc Source #

Outputable PkgQual Source # 
Instance details

Defined in GHC.Types.PkgQual

Methods

ppr :: PkgQual -> SDoc Source #

Outputable RawPkgQual Source # 
Instance details

Defined in GHC.Types.PkgQual

Methods

ppr :: RawPkgQual -> SDoc Source #

Outputable SlotTy Source # 
Instance details

Defined in GHC.Types.RepType

Methods

ppr :: SlotTy -> SDoc Source #

Outputable IfaceTrustInfo Source # 
Instance details

Defined in GHC.Types.SafeHaskell

Outputable SafeHaskellMode Source # 
Instance details

Defined in GHC.Types.SafeHaskell

Outputable FractionalLit Source # 
Instance details

Defined in GHC.Types.SourceText

Outputable IntegralLit Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: IntegralLit -> SDoc Source #

Outputable SourceText Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: SourceText -> SDoc Source #

Outputable StringLiteral Source # 
Instance details

Defined in GHC.Types.SourceText

Outputable RealSrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcLoc -> SDoc Source #

Outputable RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc Source #

Outputable SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc Source #

Outputable SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc Source #

Outputable UnhelpfulSpanReason Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable Target Source # 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: Target -> SDoc Source #

Outputable TargetId Source # 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: TargetId -> SDoc Source #

Outputable TickishPlacement Source # 
Instance details

Defined in GHC.Types.Tickish

Outputable TyThing Source # 
Instance details

Defined in GHC.Types.TyThing

Methods

ppr :: TyThing -> SDoc Source #

Outputable Unique Source # 
Instance details

Defined in GHC.Types.Unique

Methods

ppr :: Unique -> SDoc Source #

Outputable AnonArgFlag Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: AnonArgFlag -> SDoc Source #

Outputable ArgFlag Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: ArgFlag -> SDoc Source #

Outputable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc Source #

Outputable InScopeSet Source # 
Instance details

Defined in GHC.Types.Var.Env

Methods

ppr :: InScopeSet -> SDoc Source #

Outputable HomeUnitEnv Source # 
Instance details

Defined in GHC.Unit.Env

Methods

ppr :: HomeUnitEnv -> SDoc Source #

Outputable PackageId Source # 
Instance details

Defined in GHC.Unit.Info

Methods

ppr :: PackageId -> SDoc Source #

Outputable PackageName Source # 
Instance details

Defined in GHC.Unit.Info

Methods

ppr :: PackageName -> SDoc Source #

Outputable ModNodeKeyWithUid Source # 
Instance details

Defined in GHC.Unit.Module.Graph

Outputable ModuleGraphNode Source # 
Instance details

Defined in GHC.Unit.Module.Graph

Outputable NodeKey Source # 
Instance details

Defined in GHC.Unit.Module.Graph

Methods

ppr :: NodeKey -> SDoc Source #

Outputable ModLocation Source # 
Instance details

Defined in GHC.Unit.Module.Location

Methods

ppr :: ModLocation -> SDoc Source #

Outputable ModSummary Source # 
Instance details

Defined in GHC.Unit.Module.ModSummary

Methods

ppr :: ModSummary -> SDoc Source #

Outputable ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

Methods

ppr :: ModuleName -> SDoc Source #

Outputable HscBackendAction Source # 
Instance details

Defined in GHC.Unit.Module.Status

Outputable UnitPprInfo Source # 
Instance details

Defined in GHC.Unit.Ppr

Methods

ppr :: UnitPprInfo -> SDoc Source #

Outputable ModuleOrigin Source # 
Instance details

Defined in GHC.Unit.State

Outputable UnitErr Source # 
Instance details

Defined in GHC.Unit.State

Methods

ppr :: UnitErr -> SDoc Source #

Outputable UnusableUnitReason Source # 
Instance details

Defined in GHC.Unit.State

Outputable InstalledModule Source # 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedModule Source # 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedUnit Source # 
Instance details

Defined in GHC.Unit.Types

Outputable Module Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc Source #

Outputable Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc Source #

Outputable UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: UnitId -> SDoc Source #

Outputable PprStyle Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: PprStyle -> SDoc Source #

Outputable QualifyName Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: QualifyName -> SDoc Source #

Outputable SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc Source #

Outputable ForeignExport Source # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Outputable ForeignImport Source # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Outputable NewOrData Source # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: NewOrData -> SDoc Source #

Outputable HsArrowMatchContext Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable LamCaseVariant Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable SpliceDecoration Source # 
Instance details

Defined in Language.Haskell.Syntax.Expr

Outputable DataConCantHappen Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Outputable NoExtField Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

ppr :: NoExtField -> SDoc Source #

Outputable OverLitVal Source # 
Instance details

Defined in Language.Haskell.Syntax.Lit

Methods

ppr :: OverLitVal -> SDoc Source #

Outputable HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsIPName -> SDoc Source #

Outputable HsTyLit Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsTyLit -> SDoc Source #

Outputable Ordering Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Ordering -> SDoc Source #

Outputable UTCTime Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: UTCTime -> SDoc Source #

Outputable Integer Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Integer -> SDoc Source #

Outputable () Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: () -> SDoc Source #

Outputable Bool Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Bool -> SDoc Source #

Outputable Char Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Char -> SDoc Source #

Outputable Double Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Double -> SDoc Source #

Outputable Float Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Float -> SDoc Source #

Outputable Int Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int -> SDoc Source #

Outputable Word Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word -> SDoc Source #

Outputable a => Outputable (SCC a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SCC a -> SDoc Source #

Outputable elt => Outputable (IntMap elt) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: IntMap elt -> SDoc Source #

Outputable a => Outputable (Set a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Set a -> SDoc Source #

Outputable instr => Outputable (GenBasicBlock instr) Source # 
Instance details

Defined in GHC.Cmm

Methods

ppr :: GenBasicBlock instr -> SDoc Source #

Outputable instr => Outputable (ListGraph instr) Source # 
Instance details

Defined in GHC.Cmm

Methods

ppr :: ListGraph instr -> SDoc Source #

Outputable a => Outputable (LabelMap a) Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: LabelMap a -> SDoc Source #

OutputableBndr b => Outputable (Alt b) Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: Alt b -> SDoc Source #

OutputableBndr b => Outputable (Bind b) Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: Bind b -> SDoc Source #

OutputableBndr b => Outputable (Expr b) Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: Expr b -> SDoc Source #

Outputable b => Outputable (TaggedBndr b) Source # 
Instance details

Defined in GHC.Core

Methods

ppr :: TaggedBndr b -> SDoc Source #

Outputable ev => Outputable (NormaliseStepResult ev) Source # 
Instance details

Defined in GHC.Core.Coercion

Outputable (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiom br -> SDoc Source #

Outputable a => Outputable (CoreMap a) Source # 
Instance details

Defined in GHC.Core.Map.Expr

Methods

ppr :: CoreMap a -> SDoc Source #

Outputable a => Outputable (TypeMapG a) Source # 
Instance details

Defined in GHC.Core.Map.Type

Methods

ppr :: TypeMapG a -> SDoc Source #

Outputable a => Outputable (RoughMap a) Source # 
Instance details

Defined in GHC.Core.RoughMap

Methods

ppr :: RoughMap a -> SDoc Source #

Outputable a => Outputable (Scaled a) Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc Source #

Outputable a => Outputable (UnifyResultM a) Source # 
Instance details

Defined in GHC.Core.Unify

Methods

ppr :: UnifyResultM a -> SDoc Source #

Outputable a => Outputable (Bag a) Source # 
Instance details

Defined in GHC.Data.Bag

Methods

ppr :: Bag a -> SDoc Source #

OutputableBndr a => Outputable (BooleanFormula a) Source # 
Instance details

Defined in GHC.Data.BooleanFormula

Methods

ppr :: BooleanFormula a -> SDoc Source #

Outputable node => Outputable (Graph node) Source # 
Instance details

Defined in GHC.Data.Graph.Directed

Methods

ppr :: Graph node -> SDoc Source #

Outputable a => Outputable (OrdList a) Source # 
Instance details

Defined in GHC.Data.OrdList

Methods

ppr :: OrdList a -> SDoc Source #

Outputable a => Outputable (Pair a) Source # 
Instance details

Defined in GHC.Data.Pair

Methods

ppr :: Pair a -> SDoc Source #

Outputable (KnotVars a) Source # 
Instance details

Defined in GHC.Driver.Env.KnotVars

Methods

ppr :: KnotVars a -> SDoc Source #

OutputableBndrId p => Outputable (IE (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: IE (GhcPass p) -> SDoc Source #

OutputableBndr name => Outputable (IEWrappedName name) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: IEWrappedName name -> SDoc Source #

(OutputableBndrId p, Outputable (Anno (IE (GhcPass p))), Outputable (ImportDeclPkgQual (GhcPass p))) => Outputable (ImportDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: ImportDecl (GhcPass p) -> SDoc Source #

Outputable a => Outputable (CheckResult a) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: CheckResult a -> SDoc Source #

Outputable p => Outputable (PmGRHS p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGRHS p -> SDoc Source #

Outputable p => Outputable (PmGRHSs p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGRHSs p -> SDoc Source #

Outputable p => Outputable (PmMatch p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmMatch p -> SDoc Source #

Outputable p => Outputable (PmMatchGroup p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmMatchGroup p -> SDoc Source #

Outputable p => Outputable (PmPatBind p) Source # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmPatBind p -> SDoc Source #

Outputable a => Outputable (EpAnn a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpAnn a -> SDoc Source #

Outputable a => Outputable (SrcSpanAnn' a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: SrcSpanAnn' a -> SDoc Source #

Outputable (PatBuilder GhcPs) Source # 
Instance details

Defined in GHC.Parser.Types

OutputablePass pass => Outputable (GenStgBinding pass) Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: GenStgBinding pass -> SDoc Source #

OutputablePass pass => Outputable (GenStgExpr pass) Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: GenStgExpr pass -> SDoc Source #

OutputablePass pass => Outputable (GenStgRhs pass) Source # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: GenStgRhs pass -> SDoc Source #

Outputable name => Outputable (AnnTarget name) Source # 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: AnnTarget name -> SDoc Source #

Outputable (DefMethSpec ty) Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: DefMethSpec ty -> SDoc Source #

Diagnostic e => Outputable (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Messages e -> SDoc Source #

Outputable a => Outputable (OccEnv a) Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc Source #

Outputable e => Outputable (Located e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc Source #

Outputable (XTickishId pass) => Outputable (GenTickish pass) Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: GenTickish pass -> SDoc Source #

Outputable a => Outputable (UniqDSet a) Source # 
Instance details

Defined in GHC.Types.Unique.DSet

Methods

ppr :: UniqDSet a -> SDoc Source #

Outputable a => Outputable (UniqSet a) Source # 
Instance details

Defined in GHC.Types.Unique.Set

Methods

ppr :: UniqSet a -> SDoc Source #

Outputable (UnitEnvGraph HomeUnitEnv) Source # 
Instance details

Defined in GHC.Unit.Env

Outputable elt => Outputable (InstalledModuleEnv elt) Source # 
Instance details

Defined in GHC.Unit.Module.Env

Outputable a => Outputable (ModuleEnv a) Source # 
Instance details

Defined in GHC.Unit.Module.Env

Methods

ppr :: ModuleEnv a -> SDoc Source #

Outputable (WarningTxt pass) Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

ppr :: WarningTxt pass -> SDoc Source #

Outputable u => Outputable (UnitDatabase u) Source # 
Instance details

Defined in GHC.Unit.State

Methods

ppr :: UnitDatabase u -> SDoc Source #

Outputable unit => Outputable (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Definite unit -> SDoc Source #

Outputable a => Outputable (GenWithIsBoot a) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: GenWithIsBoot a -> SDoc Source #

OutputableBndrId p => Outputable (FixitySig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: FixitySig (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsIPBinds (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: HsIPBinds (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (IPBind (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: IPBind (GhcPass p) -> SDoc Source #

Outputable (XRec a RdrName) => Outputable (RecordPatSynField a) Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds

OutputableBndrId p => Outputable (Sig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: Sig (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (AnnDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: AnnDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (ClsInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: ClsInstDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (ConDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: ConDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (DataFamInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (DefaultDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: DefaultDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (DerivDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: DerivDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (DerivStrategy (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Outputable (DocDecl name) Source # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: DocDecl name -> SDoc Source #

OutputableBndrId p => Outputable (FamilyDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: FamilyDecl (GhcPass p) -> SDoc Source #

Outputable (FamilyInfo pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: FamilyInfo pass -> SDoc Source #

OutputableBndrId p => Outputable (ForeignDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: ForeignDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (FunDep (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: FunDep (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsDataDefn (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: HsDataDefn (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: HsDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsDerivingClause (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (HsGroup (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: HsGroup (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (InstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: InstDecl (GhcPass p) -> SDoc Source #

OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (RuleBndr (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: RuleBndr (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (RuleDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: RuleDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (RuleDecls (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: RuleDecls (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (SpliceDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: SpliceDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (TyClDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: TyClDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (TyClGroup (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: TyClGroup (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (TyFamInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (WarnDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: WarnDecl (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (WarnDecls (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: WarnDecls (GhcPass p) -> SDoc Source #

OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: ApplicativeArg (GhcPass idL) -> SDoc Source #

OutputableBndrId p => Outputable (ArithSeqInfo (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: ArithSeqInfo (GhcPass p) -> SDoc Source #

UnXRec p => Outputable (DotFieldOcc p) Source # 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

ppr :: DotFieldOcc p -> SDoc Source #

(UnXRec p, Outputable (XRec p FieldLabelString)) => Outputable (FieldLabelStrings p) Source # 
Instance details

Defined in Language.Haskell.Syntax.Expr

OutputableBndrId p => Outputable (HsCmd (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsCmd (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsCmdTop (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsCmdTop (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsExpr (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsExpr (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsMatchContext (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable (HsPragE (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsPragE (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsQuote (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsQuote (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsSplice (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsSplice (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsSplicedThing (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsStmtContext (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable (HsLit (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Lit

Methods

ppr :: HsLit (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsOverLit (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Lit

Methods

ppr :: HsOverLit (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: Pat (GhcPass p) -> SDoc Source #

Outputable (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: ConDeclField (GhcPass p) -> SDoc Source #

Outputable (XRec pass RdrName) => Outputable (FieldOcc pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: FieldOcc pass -> SDoc Source #

OutputableBndrId pass => Outputable (HsArrow (GhcPass pass)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsArrow (GhcPass pass) -> SDoc Source #

OutputableBndrId p => Outputable (HsForAllTelescope (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndrId p => Outputable (HsPatSigType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsPatSigType (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsSigType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsSigType (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsType (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: LHsQTyVars (GhcPass p) -> SDoc Source #

Outputable a => Outputable (NonEmpty a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: NonEmpty a -> SDoc Source #

Outputable a => Outputable (Maybe a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Maybe a -> SDoc Source #

Outputable a => Outputable [a] Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: [a] -> SDoc Source #

(Outputable a, Outputable b) => Outputable (Either a b) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Either a b -> SDoc Source #

(Outputable key, Outputable elt) => Outputable (Map key elt) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Map key elt -> SDoc Source #

(Outputable a, Outputable b) => Outputable (Node a b) Source # 
Instance details

Defined in GHC.Data.Graph.Directed

Methods

ppr :: Node a b -> SDoc Source #

(Outputable a, Outputable (m a)) => Outputable (GenMap m a) Source # 
Instance details

Defined in GHC.Data.TrieMap

Methods

ppr :: GenMap m a -> SDoc Source #

(TrieMap m, Outputable a) => Outputable (ListMap m a) Source # 
Instance details

Defined in GHC.Data.TrieMap

Methods

ppr :: ListMap m a -> SDoc Source #

Outputable a => Outputable (WithHsDocIdentifiers a pass) Source #

For compatibility with the existing @-ddump-parsed' output, we only show the docstring.

Use pprHsDoc to show HsDoc's internals.

Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: WithHsDocIdentifiers a pass -> SDoc Source #

(Outputable a, Outputable b) => Outputable (HsExpansion a b) Source #

Just print the original expression (the a).

Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsExpansion a b -> SDoc Source #

(Outputable a, Outputable b) => Outputable (HsPatExpansion a b) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsPatExpansion a b -> SDoc Source #

Outputable (GenLocated Anchor EpaComment) Source # 
Instance details

Defined in GHC.Parser.Annotation

(Outputable a, Outputable e) => Outputable (GenLocated (SrcSpanAnn' a) e) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: GenLocated (SrcSpanAnn' a) e -> SDoc Source #

Outputable e => Outputable (GenLocated RealSrcSpan e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable a => Outputable (UniqDFM key a) Source # 
Instance details

Defined in GHC.Types.Unique.DFM

Methods

ppr :: UniqDFM key a -> SDoc Source #

Outputable a => Outputable (UniqFM key a) Source # 
Instance details

Defined in GHC.Types.Unique.FM

Methods

ppr :: UniqFM key a -> SDoc Source #

(Outputable k, Outputable a) => Outputable (UniqMap k a) Source # 
Instance details

Defined in GHC.Types.Unique.Map

Methods

ppr :: UniqMap k a -> SDoc Source #

(Outputable key, Outputable ele) => Outputable (UniqSDFM key ele) Source # 
Instance details

Defined in GHC.Types.Unique.SDFM

Methods

ppr :: UniqSDFM key ele -> SDoc Source #

OutputableBndr tv => Outputable (VarBndr tv TyConBndrVis) Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable tv => Outputable (VarBndr tv ArgFlag) Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv ArgFlag -> SDoc Source #

Outputable tv => Outputable (VarBndr tv Specificity) Source # 
Instance details

Defined in GHC.Types.Var

(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: HsBindLR (GhcPass pl) (GhcPass pr) -> SDoc Source #

(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: HsLocalBindsLR (GhcPass pl) (GhcPass pr) -> SDoc Source #

(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsValBindsLR (GhcPass pl) (GhcPass pr)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: HsValBindsLR (GhcPass pl) (GhcPass pr) -> SDoc Source #

(OutputableBndrId l, OutputableBndrId r) => Outputable (PatSynBind (GhcPass l) (GhcPass r)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: PatSynBind (GhcPass l) (GhcPass r) -> SDoc Source #

(OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: Match (GhcPass pr) body -> SDoc Source #

(Outputable (StmtLR (GhcPass idL) (GhcPass idL) (LHsExpr (GhcPass idL))), Outputable (XXParStmtBlock (GhcPass idL) (GhcPass idR))) => Outputable (ParStmtBlock (GhcPass idL) (GhcPass idR)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: ParStmtBlock (GhcPass idL) (GhcPass idR) -> SDoc Source #

(Outputable p, OutputableBndr p, Outputable arg) => Outputable (HsFieldBind p arg) Source # 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

ppr :: HsFieldBind p arg -> SDoc Source #

(Outputable arg, Outputable (XRec p (HsRecField p arg))) => Outputable (HsRecFields p arg) Source # 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

ppr :: HsRecFields p arg -> SDoc Source #

(Outputable tm, Outputable ty) => Outputable (HsArg tm ty) Source #

This instance is meant for debug-printing purposes. If you wish to pretty-print an application of HsArgs, use pprHsArgsApp instead.

Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsArg tm ty -> SDoc Source #

(OutputableBndrFlag flag p, OutputableBndrFlag flag (NoGhcTcPass p), OutputableBndrId p) => Outputable (HsOuterTyVarBndrs flag (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsOuterTyVarBndrs flag (GhcPass p) -> SDoc Source #

(OutputableBndrId p, OutputableBndrFlag flag p) => Outputable (HsTyVarBndr flag (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsTyVarBndr flag (GhcPass p) -> SDoc Source #

Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsWildCardBndrs (GhcPass p) thing -> SDoc Source #

(Outputable a, Outputable b) => Outputable (a, b) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b) -> SDoc Source #

(OutputableBndrId pl, OutputableBndrId pr, Anno (StmtLR (GhcPass pl) (GhcPass pr) body) ~ SrcSpanAnnA, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: StmtLR (GhcPass pl) (GhcPass pr) body -> SDoc Source #

(Outputable tyarg, Outputable arg, Outputable rec) => Outputable (HsConDetails tyarg arg rec) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsConDetails tyarg arg rec -> SDoc Source #

(Outputable a, Outputable b, Outputable c) => Outputable (a, b, c) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c) -> SDoc Source #

(Outputable a, Outputable b, Outputable c, Outputable d) => Outputable (a, b, c, d) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d) -> SDoc Source #

(Outputable a, Outputable b, Outputable c, Outputable d, Outputable e) => Outputable (a, b, c, d, e) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d, e) -> SDoc Source #

(Outputable a, Outputable b, Outputable c, Outputable d, Outputable e, Outputable f) => Outputable (a, b, c, d, e, f) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d, e, f) -> SDoc Source #

(Outputable a, Outputable b, Outputable c, Outputable d, Outputable e, Outputable f, Outputable g) => Outputable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d, e, f, g) -> SDoc Source #

class Outputable a => OutputableBndr a where Source #

When we print a binder, we often want to print its type too. The OutputableBndr class encapsulates this idea.

Minimal complete definition

pprPrefixOcc, pprInfixOcc

Instances

Instances details
OutputableBndr ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

OutputableBndr DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

OutputableBndr PatSyn Source # 
Instance details

Defined in GHC.Core.PatSyn

OutputableBndr Name Source # 
Instance details

Defined in GHC.Types.Name

OutputableBndr OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

OutputableBndr RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

OutputableBndr Var Source # 
Instance details

Defined in GHC.Core.Ppr

OutputableBndr HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Outputable b => OutputableBndr (TaggedBndr b) Source # 
Instance details

Defined in GHC.Core.Ppr

OutputableBndr name => OutputableBndr (IEWrappedName name) Source # 
Instance details

Defined in GHC.Hs.ImpExp

(UnXRec p, Outputable (XRec p FieldLabelString)) => OutputableBndr (Located (FieldLabelStrings p)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Expr

OutputableBndr (Located (AmbiguousFieldOcc (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.Type

(UnXRec p, Outputable (XRec p FieldLabelString)) => OutputableBndr (FieldLabelStrings p) Source # 
Instance details

Defined in Language.Haskell.Syntax.Expr

OutputableBndr (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

(UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (FieldOcc pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

(Outputable a, OutputableBndr e) => OutputableBndr (GenLocated (SrcSpanAnn' a) e) Source # 
Instance details

Defined in GHC.Parser.Annotation

(UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

OutputableBndr (Id, TagSig) Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

class OutputableP env a where Source #

Outputable class with an additional environment value

See Note [The OutputableP class]

Methods

pdoc :: env -> a -> SDoc Source #

Instances

Instances details
OutputableP Platform CLabel Source # 
Instance details

Defined in GHC.Cmm.CLabel

Methods

pdoc :: Platform -> CLabel -> SDoc Source #

OutputableP env Label Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

pdoc :: env -> Label -> SDoc Source #

OutputableP env Alignment Source # 
Instance details

Defined in GHC.Types.Basic

Methods

pdoc :: env -> Alignment -> SDoc Source #

OutputableP env SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> SDoc -> SDoc Source #

OutputableP env a => OutputableP env (SCC a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> SCC a -> SDoc Source #

OutputableP env a => OutputableP env (Set a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> Set a -> SDoc Source #

OutputableP env instr => OutputableP env (GenBasicBlock instr) Source # 
Instance details

Defined in GHC.Cmm

Methods

pdoc :: env -> GenBasicBlock instr -> SDoc Source #

OutputableP env instr => OutputableP env (ListGraph instr) Source # 
Instance details

Defined in GHC.Cmm

Methods

pdoc :: env -> ListGraph instr -> SDoc Source #

OutputableP env a => OutputableP env (LabelMap a) Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

pdoc :: env -> LabelMap a -> SDoc Source #

Outputable a => OutputableP env (PDoc a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> PDoc a -> SDoc Source #

OutputableP env a => OutputableP env (Maybe a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> Maybe a -> SDoc Source #

OutputableP env a => OutputableP env [a] Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> [a] -> SDoc Source #

(OutputableP env key, OutputableP env elt) => OutputableP env (Map key elt) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> Map key elt -> SDoc Source #

(OutputableP env a, OutputableP env b) => OutputableP env (a, b) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> (a, b) -> SDoc Source #

(OutputableP env a, OutputableP env b, OutputableP env c) => OutputableP env (a, b, c) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> (a, b, c) -> SDoc Source #

Pretty printing combinators

data SDoc Source #

Represents a pretty-printable document.

To display an SDoc, use printSDoc, printSDocLn, bufLeftRenderSDoc, or renderWithContext. Avoid calling runSDoc directly as it breaks the abstraction layer.

Instances

Instances details
IsString SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

fromString :: String -> SDoc #

Outputable SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc Source #

OutputableP env SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> SDoc -> SDoc Source #

newtype PDoc a Source #

Wrapper for types having a Outputable instance when an OutputableP instance is required.

Constructors

PDoc a 

Instances

Instances details
Outputable a => OutputableP env (PDoc a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> PDoc a -> SDoc Source #

interppSP :: Outputable a => [a] -> SDoc Source #

Returns the separated concatenation of the pretty printed things.

interpp'SP :: Outputable a => [a] -> SDoc Source #

Returns the comma-separated concatenation of the pretty printed things.

interpp'SP' :: (a -> SDoc) -> [a] -> SDoc Source #

pprQuotedList :: Outputable a => [a] -> SDoc Source #

Returns the comma-separated concatenation of the quoted pretty printed things.

[x,y,z]  ==>  `x', `y', `z'

pprWithCommas Source #

Arguments

:: (a -> SDoc)

The pretty printing function to use

-> [a]

The things to be pretty printed

-> SDoc

SDoc where the things have been pretty printed, comma-separated and finally packed into a paragraph.

pprWithBars Source #

Arguments

:: (a -> SDoc)

The pretty printing function to use

-> [a]

The things to be pretty printed

-> SDoc

SDoc where the things have been pretty printed, bar-separated and finally packed into a paragraph.

nest :: Int -> SDoc -> SDoc Source #

Indent SDoc some specified amount

doublePrec :: Int -> Double -> SDoc Source #

doublePrec p n shows a floating point number n with p digits of precision after the decimal point.

(<>) :: SDoc -> SDoc -> SDoc Source #

Join two SDoc together horizontally without a gap

(<+>) :: SDoc -> SDoc -> SDoc Source #

Join two SDoc together horizontally with a gap between them

hcat :: [SDoc] -> SDoc Source #

Concatenate SDoc horizontally

hsep :: [SDoc] -> SDoc Source #

Concatenate SDoc horizontally with a space between each one

($$) :: SDoc -> SDoc -> SDoc Source #

Join two SDoc together vertically; if there is no vertical overlap it "dovetails" the two onto one line

($+$) :: SDoc -> SDoc -> SDoc Source #

Join two SDoc together vertically

vcat :: [SDoc] -> SDoc Source #

Concatenate SDoc vertically with dovetailing

sep :: [SDoc] -> SDoc Source #

Separate: is either like hsep or like vcat, depending on what fits

cat :: [SDoc] -> SDoc Source #

Catenate: is either like hcat or like vcat, depending on what fits

fsep :: [SDoc] -> SDoc Source #

A paragraph-fill combinator. It's much like sep, only it keeps fitting things on one line until it can't fit any more.

fcat :: [SDoc] -> SDoc Source #

This behaves like fsep, but it uses <> for horizontal conposition rather than <+>

hang Source #

Arguments

:: SDoc

The header

-> Int

Amount to indent the hung body

-> SDoc

The hung body, indented and placed below the header

-> SDoc 

hangNotEmpty :: SDoc -> Int -> SDoc -> SDoc Source #

This behaves like hang, but does not indent the second document when the header is empty.

punctuate Source #

Arguments

:: SDoc

The punctuation

-> [SDoc]

The list that will have punctuation added between every adjacent pair of elements

-> [SDoc]

Punctuated list

speakNth :: Int -> SDoc Source #

Converts an integer to a verbal index:

speakNth 1 = text "first"
speakNth 5 = text "fifth"
speakNth 21 = text "21st"

speakN :: Int -> SDoc Source #

Converts an integer to a verbal multiplicity:

speakN 0 = text "none"
speakN 5 = text "five"
speakN 10 = text "10"

speakNOf :: Int -> SDoc -> SDoc Source #

Converts an integer and object description to a statement about the multiplicity of those objects:

speakNOf 0 (text "melon") = text "no melons"
speakNOf 1 (text "melon") = text "one melon"
speakNOf 3 (text "melon") = text "three melons"

plural :: [a] -> SDoc Source #

Determines the pluralisation suffix appropriate for the length of a list:

plural [] = char 's'
plural ["Hello"] = empty
plural ["Hello", "World"] = char 's'

singular :: [a] -> SDoc Source #

Determines the singular verb suffix appropriate for the length of a list:

singular [] = empty
singular["Hello"] = char 's'
singular ["Hello", "World"] = empty

isOrAre :: [a] -> SDoc Source #

Determines the form of to be appropriate for the length of a list:

isOrAre [] = text "are"
isOrAre ["Hello"] = text "is"
isOrAre ["Hello", "World"] = text "are"

doOrDoes :: [a] -> SDoc Source #

Determines the form of to do appropriate for the length of a list:

doOrDoes [] = text "do"
doOrDoes ["Hello"] = text "does"
doOrDoes ["Hello", "World"] = text "do"

itsOrTheir :: [a] -> SDoc Source #

Determines the form of possessive appropriate for the length of a list:

itsOrTheir [x]   = text "its"
itsOrTheir [x,y] = text "their"
itsOrTheir []    = text "their"  -- probably avoid this

thisOrThese :: [a] -> SDoc Source #

Determines the form of subject appropriate for the length of a list:

thisOrThese [x]   = text "This"
thisOrThese [x,y] = text "These"
thisOrThese []    = text "These"  -- probably avoid this

hasOrHave :: [a] -> SDoc Source #

"has" or "have" depending on the length of a list.

coloured :: PprColour -> SDoc -> SDoc Source #

Apply the given colour/style for the argument.

Only takes effect if colours are enabled.

Converting SDoc into strings and outputting it

printSDoc :: SDocContext -> Mode -> Handle -> SDoc -> IO () Source #

The analog of printDoc_ for SDoc, which tries to make sure the terminal doesn't get screwed up by the ANSI color codes if an exception is thrown during pretty-printing.

printSDocLn :: SDocContext -> Mode -> Handle -> SDoc -> IO () Source #

Like printSDoc but appends an extra newline.

bufLeftRenderSDoc :: SDocContext -> BufHandle -> SDoc -> IO () Source #

An efficient variant of printSDoc specialized for LeftMode that outputs to a BufHandle.

pprHsChar :: Char -> SDoc Source #

Special combinator for showing character literals.

pprHsString :: FastString -> SDoc Source #

Special combinator for showing string literals.

pprHsBytes :: ByteString -> SDoc Source #

Special combinator for showing bytestring literals.

pprPrimChar :: Char -> SDoc Source #

Special combinator for showing unboxed literals.

pprFilePathString :: FilePath -> SDoc Source #

Normalise, escape and render a string representing a path

e.g. "c:\whatever"

Controlling the style in which output is printed

data BindingSite Source #

BindingSite is used to tell the thing that prints binder what language construct is binding the identifier. This can be used to decide how much info to print. Also see Note [Binding-site specific printing] in GHC.Core.Ppr

Constructors

LambdaBind

The x in (x. e)

CaseBind

The x in case scrut of x { (y,z) -> ... }

CasePatBind

The y,z in case scrut of x { (y,z) -> ... }

LetBind

The x in (let x = rhs in e)

Instances

Instances details
Eq BindingSite Source # 
Instance details

Defined in GHC.Utils.Outputable

data PprStyle Source #

Constructors

PprUser PrintUnqualified Depth Coloured 
PprDump PrintUnqualified 
PprCode !LabelStyle

Print code; either C or assembler

Instances

Instances details
Outputable PprStyle Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: PprStyle -> SDoc Source #

data LabelStyle Source #

Style of label pretty-printing.

When we produce C sources or headers, we have to take into account that C compilers transform C labels when they convert them into symbols. For example, they can add prefixes (e.g., "_" on Darwin) or suffixes (size for stdcalls on Windows). So we provide two ways to pretty-print CLabels: C style or Asm style.

Constructors

CStyle

C label style (used by C and LLVM backends)

AsmStyle

Asm label style (used by NCG backend)

data PrintUnqualified Source #

When printing code that contains original names, we need to map the original names back to something the user understands. This is the purpose of the triple of functions that gets passed around when rendering SDoc.

type QueryQualifyName = Module -> OccName -> QualifyName Source #

Given a Name's Module and OccName, decide whether and how to qualify it.

type QueryQualifyModule = Module -> Bool Source #

For a given module, we need to know whether to print it with a package name to disambiguate it.

type QueryQualifyPackage = Unit -> Bool Source #

For a given package, we need to know whether to print it with the component id to disambiguate it.

alwaysQualifyNames :: QueryQualifyName Source #

NB: This won't ever show package IDs

data QualifyName Source #

Instances

Instances details
Outputable QualifyName Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: QualifyName -> SDoc Source #

sdocOption :: (SDocContext -> a) -> (a -> SDoc) -> SDoc Source #

data SDocContext Source #

Constructors

SDC 

Fields

defaultSDocContext :: SDocContext Source #

Default pretty-printing options

pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc Source #

Truncate a list that is longer than the current depth.

mkErrStyle :: PrintUnqualified -> PprStyle Source #

Style for printing error messages

defaultErrStyle :: PprStyle Source #

Default style for error messages, when we don't know PrintUnqualified It's a bit of a hack because it doesn't take into account what's in scope Only used for desugarer warnings, and typechecker errors in interface sigs

data Depth Source #

Constructors

AllTheWay 
PartWay Int

0 => stop

DefaultDepth

Use sdocDefaultDepth field as depth

ifPprDebug :: SDoc -> SDoc -> SDoc Source #

Says what to do with and without -dppr-debug

whenPprDebug :: SDoc -> SDoc Source #

Says what to do with -dppr-debug; without, return empty

getPprDebug :: (Bool -> SDoc) -> SDoc Source #

Indicate if -dppr-debug mode is enabled