ghc-9.0.2: The GHC API
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

Minimal complete definition

Nothing

Methods

ppr :: a -> SDoc Source #

pprPrec :: Rational -> a -> SDoc Source #

Instances

Instances details
Outputable Fingerprint Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Int32 Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Int64 Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Word16 Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Word32 Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Word64 Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable CoreModule Source # 
Instance details

Defined in GHC

Outputable PrimCall Source # 
Instance details

Defined in GHC.Builtin.PrimOps

Outputable PrimOp Source # 
Instance details

Defined in GHC.Builtin.PrimOps

Outputable BCInstr Source # 
Instance details

Defined in GHC.ByteCode.Instr

Outputable CgBreakInfo Source # 
Instance details

Defined in GHC.ByteCode.Types

Outputable CompiledByteCode Source # 
Instance details

Defined in GHC.ByteCode.Types

Outputable UnlinkedBCO Source # 
Instance details

Defined in GHC.ByteCode.Types

Outputable CmmGraph Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable CmmInfoTable Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

Outputable CmmStackInfo Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable CmmStatic Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

Outputable CmmTopInfo Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable CLabel Source # 
Instance details

Defined in GHC.Cmm.CLabel

Outputable ForeignLabelSource Source # 
Instance details

Defined in GHC.Cmm.CLabel

Outputable ParamLocation Source # 
Instance details

Defined in GHC.Cmm.CallConv

Outputable Label Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Outputable LabelSet Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Outputable DebugBlock Source # 
Instance details

Defined in GHC.Cmm.DebugBlock

Outputable UnwindExpr Source # 
Instance details

Defined in GHC.Cmm.DebugBlock

Outputable UnwindPoint Source # 
Instance details

Defined in GHC.Cmm.DebugBlock

Outputable Area Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Outputable CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Outputable CmmLit Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Outputable CmmReg Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Outputable GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Outputable LocalReg Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Outputable ModuleSRTInfo Source # 
Instance details

Defined in GHC.Cmm.Info.Build

Outputable CmmReturnInfo Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable CmmTickScope Source # 
Instance details

Defined in GHC.Cmm.Node

Outputable Convention Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable ForeignConvention Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable ForeignTarget Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable Status Source # 
Instance details

Defined in GHC.Cmm.ProcPoint

Outputable CmmType Source # 
Instance details

Defined in GHC.Cmm.Type

Outputable ForeignHint Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

Outputable Width Source # 
Instance details

Defined in GHC.Cmm.Type

Outputable CfgEdge Source # 
Instance details

Defined in GHC.CmmToAsm.CFG

Outputable EdgeInfo Source # 
Instance details

Defined in GHC.CmmToAsm.CFG

Outputable EdgeWeight Source # 
Instance details

Defined in GHC.CmmToAsm.CFG

Outputable DwarfFrameBlock Source # 
Instance details

Defined in GHC.CmmToAsm.Dwarf.Types

Outputable Instr Source # 
Instance details

Defined in GHC.CmmToAsm.PPC.Ppr

Outputable JumpDest Source # 
Instance details

Defined in GHC.CmmToAsm.PPC.RegInfo

Outputable SpillStats Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Graph.Spill

Outputable Loc Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.Base

Methods

ppr :: Loc -> SDoc Source #

pprPrec :: Rational -> Loc -> SDoc Source #

Outputable FreeRegs Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.PPC

Outputable FreeRegs Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.SPARC

Outputable FreeRegs Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.X86

Outputable FreeRegs Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.X86_64

Outputable LiveInfo Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Outputable Instr Source # 
Instance details

Defined in GHC.CmmToAsm.SPARC.Ppr

Outputable JumpDest Source # 
Instance details

Defined in GHC.CmmToAsm.SPARC.ShortcutJump

Outputable Instr Source # 
Instance details

Defined in GHC.CmmToAsm.X86.Ppr

Outputable JumpDest Source # 
Instance details

Defined in GHC.CmmToAsm.X86.Instr

Outputable AltCon Source # 
Instance details

Defined in GHC.Core

Outputable CoreRule Source # 
Instance details

Defined in GHC.Core.Ppr

Outputable Unfolding Source # 
Instance details

Defined in GHC.Core.Ppr

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

Outputable LiftingContext Source # 
Instance details

Defined in GHC.Core.Coercion

Outputable CoAxBranch Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Outputable DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable EqSpec Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable HsImplBang Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable HsSrcBang Source # 
Instance details

Defined in GHC.Core.DataCon

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

Outputable FamInstMatch Source # 
Instance details

Defined in GHC.Core.FamInstEnv

Outputable ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

Outputable FloatBind Source # 
Instance details

Defined in GHC.Core.Make

Outputable IsSubmult Source # 
Instance details

Defined in GHC.Core.Multiplicity

Outputable ArityType Source # 
Instance details

Defined in GHC.Core.Opt.Arity

Outputable CoreToDo Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Outputable FloatOutSwitches Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Outputable SimplMode Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Outputable Tick Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Outputable FloatSpec Source # 
Instance details

Defined in GHC.Core.Opt.SetLevels

Outputable Level Source # 
Instance details

Defined in GHC.Core.Opt.SetLevels

Outputable LetFloats Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Env

Outputable SimplFloats Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Env

Outputable SimplSR Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Env

Outputable ArgInfo Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Outputable ArgSpec Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Outputable DupFlag Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Outputable SimplCont Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Outputable PatSyn Source # 
Instance details

Defined in GHC.Core.PatSyn

Outputable EqRel Source # 
Instance details

Defined in GHC.Core.Predicate

Outputable CoreStats Source # 
Instance details

Defined in GHC.Core.Stats

Outputable Subst Source # 
Instance details

Defined in GHC.Core.Subst

Outputable BlockSubstFlag Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable Coercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable MCoercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable TyCoBinder Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable TyLit Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable TyThing Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable Type Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable UnivCoProvenance Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable TCvSubst Source # 
Instance details

Defined in GHC.Core.TyCo.Subst

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

Outputable PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable TyConBndrVis Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable TyConFlavour Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable ArgSummary Source # 
Instance details

Defined in GHC.Core.Unfold

Outputable CallCtxt Source # 
Instance details

Defined in GHC.Core.Unfold

Outputable Usage Source # 
Instance details

Defined in GHC.Core.UsageEnv

Outputable UsageEnv Source # 
Instance details

Defined in GHC.Core.UsageEnv

Outputable FastString Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable EdgeType Source # 
Instance details

Defined in GHC.Data.Graph.Directed

Outputable UnVarGraph Source # 
Instance details

Defined in GHC.Data.Graph.UnVar

Outputable UnVarSet Source # 
Instance details

Defined in GHC.Data.Graph.UnVar

Outputable HsComponentId Source # 
Instance details

Defined in GHC.Driver.Backpack.Syntax

Outputable WarnReason Source # 
Instance details

Defined in GHC.Driver.CmdLine

Outputable Language Source # 
Instance details

Defined in GHC.Driver.Flags

Outputable WarnReason Source # 
Instance details

Defined in GHC.Driver.Flags

Outputable Phase Source # 
Instance details

Defined in GHC.Driver.Phases

Outputable PhasePlus Source # 
Instance details

Defined in GHC.Driver.Pipeline.Monad

Outputable PluginRecompile Source # 
Instance details

Defined in GHC.Driver.Plugins

Outputable GhcMode Source # 
Instance details

Defined in GHC.Driver.Session

Outputable ModRenaming Source # 
Instance details

Defined in GHC.Driver.Session

Outputable PackageArg Source # 
Instance details

Defined in GHC.Driver.Session

Outputable PackageFlag Source # 
Instance details

Defined in GHC.Driver.Session

Outputable SafeHaskellMode Source # 
Instance details

Defined in GHC.Driver.Session

Outputable CompleteMatch Source # 
Instance details

Defined in GHC.Driver.Types

Outputable FixItem Source # 
Instance details

Defined in GHC.Driver.Types

Outputable IfaceTrustInfo Source # 
Instance details

Defined in GHC.Driver.Types

Outputable InteractiveImport Source # 
Instance details

Defined in GHC.Driver.Types

Outputable ModSummary Source # 
Instance details

Defined in GHC.Driver.Types

Outputable Target Source # 
Instance details

Defined in GHC.Driver.Types

Outputable TargetId Source # 
Instance details

Defined in GHC.Driver.Types

Outputable Warnings Source # 
Instance details

Defined in GHC.Iface.Load

Outputable HsModule Source # 
Instance details

Defined in GHC.Hs

Outputable TcSpecPrag Source # 
Instance details

Defined in GHC.Hs.Binds

Outputable DocDecl Source # 
Instance details

Defined in GHC.Hs.Decls

Outputable ForeignExport Source # 
Instance details

Defined in GHC.Hs.Decls

Outputable ForeignImport Source # 
Instance details

Defined in GHC.Hs.Decls

Outputable NewOrData Source # 
Instance details

Defined in GHC.Hs.Decls

Outputable ArgDocMap Source # 
Instance details

Defined in GHC.Hs.Doc

Outputable DeclDocMap Source # 
Instance details

Defined in GHC.Hs.Doc

Outputable HsDocString Source # 
Instance details

Defined in GHC.Hs.Doc

Outputable PendingRnSplice Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable PendingTcSplice Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable SpliceDecoration 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 NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

Outputable NoExtField Source # 
Instance details

Defined in GHC.Hs.Extension

Outputable OverLitVal Source # 
Instance details

Defined in GHC.Hs.Lit

Outputable HsIPName Source # 
Instance details

Defined in GHC.Hs.Type

Outputable HsTyLit Source # 
Instance details

Defined in GHC.Hs.Type

Outputable NewHsTypeX Source # 
Instance details

Defined in GHC.Hs.Type

Outputable DsMatchContext Source # 
Instance details

Defined in GHC.HsToCore.Monad

Outputable EquationInfo Source # 
Instance details

Defined in GHC.HsToCore.Monad

Outputable PmCt Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Oracle

Outputable Delta Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable Deltas Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable PmAltCon Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable PmAltConSet Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable PmEquality Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable PmLit Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable PmLitValue Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable PossibleMatches Source # 
Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable TmState Source #

Not user-facing.

Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable TyState Source #

Not user-facing.

Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable VarInfo Source #

Not user-facing.

Instance details

Defined in GHC.HsToCore.PmCheck.Types

Outputable BindType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable ContextInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable DeclType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable EvBindDeps Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable EvVarSource Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable HieName Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable IEType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable NodeOrigin Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable RecFieldContext Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable Scope Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable TyVarScope Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable IfaceAT Source # 
Instance details

Defined in GHC.Iface.Syntax

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

Outputable IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceExpr Source # 
Instance details

Defined in GHC.Iface.Syntax

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

Outputable IfaceRule Source # 
Instance details

Defined in GHC.Iface.Syntax

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

Outputable IfaceAppArgs Source # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceBndr Source # 
Instance details

Defined in GHC.Iface.Type

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

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

Outputable IfaceType Source # 
Instance details

Defined in GHC.Iface.Type

Outputable MetaId Source # 
Instance details

Defined in GHC.Llvm.MetaData

Outputable LlvmCallConvention Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmCastOp Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmCmpOp Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmFuncAttr Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmFunctionDecl Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmLinkageType Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmMachOp Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmParamAttr Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmType Source # 
Instance details

Defined in GHC.Llvm.Types

Outputable AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnotationComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable Token Source # 
Instance details

Defined in GHC.Parser.Lexer

Outputable TyEl Source # 
Instance details

Defined in GHC.Parser.PostProcess

Outputable RealReg Source # 
Instance details

Defined in GHC.Platform.Reg

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 #

pprPrec :: Rational -> Reg -> SDoc Source #

Outputable VirtualReg Source # 
Instance details

Defined in GHC.Platform.Reg

Outputable RegClass Source # 
Instance details

Defined in GHC.Platform.Reg.Class

Outputable ChildLookupResult Source # 
Instance details

Defined in GHC.Rename.Env

Outputable HsSigCtxt Source # 
Instance details

Defined in GHC.Rename.Env

Outputable WarnUnusedForalls Source # 
Instance details

Defined in GHC.Rename.HsType

Outputable GetDocsFailure Source # 
Instance details

Defined in GHC.Runtime.Eval

Outputable Term Source # 
Instance details

Defined in GHC.Runtime.Heap.Inspect

Outputable ClosureTypeInfo Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Outputable SMRep Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Outputable StgHalfWord Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Outputable StgWord Source # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Outputable Linkable Source # 
Instance details

Defined in GHC.Runtime.Linker.Types

Outputable SptEntry Source # 
Instance details

Defined in GHC.Runtime.Linker.Types

Outputable Unlinked Source # 
Instance details

Defined in GHC.Runtime.Linker.Types

Outputable BinderInfo Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

Outputable Skeleton Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

Outputable FloatLang Source # 
Instance details

Defined in GHC.Stg.Lift.Monad

Outputable AltType 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

Outputable UpdateFlag Source # 
Instance details

Defined in GHC.Stg.Syntax

Outputable ArgRep Source # 
Instance details

Defined in GHC.StgToCmm.ArgRep

Outputable CgLoc Source # 
Instance details

Defined in GHC.StgToCmm.Closure

Outputable CgIdInfo Source # 
Instance details

Defined in GHC.StgToCmm.Monad

Outputable Sequel Source # 
Instance details

Defined in GHC.StgToCmm.Monad

Outputable ArgDescr Source # 
Instance details

Defined in GHC.StgToCmm.Types

Outputable LambdaFormInfo Source # 
Instance details

Defined in GHC.StgToCmm.Types

Outputable StandardFormInfo Source # 
Instance details

Defined in GHC.StgToCmm.Types

Outputable DerivContext Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable DerivEnv Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable DerivInstTys Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable DerivSpecMechanism Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable PredOrigin Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable ThetaOrigin Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable HoleFit Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Outputable HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Outputable TypedHole Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Outputable SAKS_or_CUSK Source # 
Instance details

Defined in GHC.Tc.Gen.HsType

Outputable LetBndrSpec Source # 
Instance details

Defined in GHC.Tc.Gen.Pat

Outputable ClsInstResult Source # 
Instance details

Defined in GHC.Tc.Instance.Class

Outputable InstanceWhat Source # 
Instance details

Defined in GHC.Tc.Instance.Class

Outputable InferMode Source # 
Instance details

Defined in GHC.Tc.Solver

Outputable FlattenMode Source # 
Instance details

Defined in GHC.Tc.Solver.Flatten

Outputable InertCans Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Outputable InertSet Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Outputable WorkList Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

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

Outputable TcIdSigInfo Source # 
Instance details

Defined in GHC.Tc.Types

Outputable TcIdSigInst Source # 
Instance details

Defined in GHC.Tc.Types

Outputable TcPatSynInfo Source # 
Instance details

Defined in GHC.Tc.Types

Outputable TcSigInfo Source # 
Instance details

Defined in GHC.Tc.Types

Outputable TcTyThing Source # 
Instance details

Defined in GHC.Tc.Types

Outputable ThStage Source # 
Instance details

Defined in GHC.Tc.Types

Outputable WhereFrom Source # 
Instance details

Defined in GHC.Tc.Types

Outputable Ct Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Ct -> SDoc Source #

pprPrec :: Rational -> Ct -> SDoc Source #

Outputable CtEvidence Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable CtFlavour Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable CtIrredStatus Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable Hole Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable HoleSort Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable ImplicStatus Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable Implication Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable QCInst Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable SubGoalDepth Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable TcEvDest Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable WantedConstraints Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable EvBind Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable EvBindMap Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable EvBindsVar Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable EvCallStack Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable EvTerm Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable EvTypeable Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable HsWrapper Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable TcEvBinds Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable CtOrigin Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Outputable SkolemInfo Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Outputable CandidatesQTvs Source # 
Instance details

Defined in GHC.Tc.Utils.TcMType

Outputable ExpType Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable InferResult Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable MetaDetails Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable MetaInfo Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable TcLevel Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable TcTyVarDetails Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable ZonkEnv Source # 
Instance details

Defined in GHC.Tc.Utils.Zonk

Outputable Rank Source # 
Instance details

Defined in GHC.Tc.Validity

Outputable Annotation Source # 
Instance details

Defined in GHC.Types.Annotations

Outputable AvailInfo Source # 
Instance details

Defined in GHC.Types.Avail

Outputable Activation Source # 
Instance details

Defined in GHC.Types.Basic

Outputable Alignment Source # 
Instance details

Defined in GHC.Types.Basic

Outputable Boxity Source # 
Instance details

Defined in GHC.Types.Basic

Outputable CompilerPhase Source # 
Instance details

Defined in GHC.Types.Basic

Outputable Fixity Source # 
Instance details

Defined in GHC.Types.Basic

Outputable FixityDirection Source # 
Instance details

Defined in GHC.Types.Basic

Outputable FractionalLit Source # 
Instance details

Defined in GHC.Types.Basic

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

Outputable IntWithInf Source # 
Instance details

Defined in GHC.Types.Basic

Outputable IntegralLit Source # 
Instance details

Defined in GHC.Types.Basic

Outputable LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Outputable LexicalFixity Source # 
Instance details

Defined in GHC.Types.Basic

Outputable OccInfo Source # 
Instance details

Defined in GHC.Types.Basic

Outputable OneShotInfo Source # 
Instance details

Defined in GHC.Types.Basic

Outputable Origin Source # 
Instance details

Defined in GHC.Types.Basic

Outputable OverlapFlag Source # 
Instance details

Defined in GHC.Types.Basic

Outputable OverlapMode Source # 
Instance details

Defined in GHC.Types.Basic

Outputable PromotionFlag Source # 
Instance details

Defined in GHC.Types.Basic

Outputable RecFlag Source # 
Instance details

Defined in GHC.Types.Basic

Outputable RuleMatchInfo Source # 
Instance details

Defined in GHC.Types.Basic

Outputable SourceText Source # 
Instance details

Defined in GHC.Types.Basic

Outputable StringLiteral Source # 
Instance details

Defined in GHC.Types.Basic

Outputable SuccessFlag Source # 
Instance details

Defined in GHC.Types.Basic

Outputable SwapFlag Source # 
Instance details

Defined in GHC.Types.Basic

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

Outputable TypeOrKind Source # 
Instance details

Defined in GHC.Types.Basic

Outputable WarningTxt Source # 
Instance details

Defined in GHC.Types.Basic

Outputable CostCentre Source # 
Instance details

Defined in GHC.Types.CostCentre

Outputable CostCentreStack Source # 
Instance details

Defined in GHC.Types.CostCentre

Outputable CprResult Source # 
Instance details

Defined in GHC.Types.Cpr

Outputable CprSig Source #

Only print the CPR result

Instance details

Defined in GHC.Types.Cpr

Outputable CprType Source # 
Instance details

Defined in GHC.Types.Cpr

Outputable Count Source # 
Instance details

Defined in GHC.Types.Demand

Outputable Divergence Source # 
Instance details

Defined in GHC.Types.Demand

Outputable DmdType Source # 
Instance details

Defined in GHC.Types.Demand

Outputable StrDmd Source # 
Instance details

Defined in GHC.Types.Demand

Outputable StrictSig Source # 
Instance details

Defined in GHC.Types.Demand

Outputable TypeShape Source # 
Instance details

Defined in GHC.Types.Demand

Outputable UseDmd Source # 
Instance details

Defined in GHC.Types.Demand

Outputable CCallConv Source # 
Instance details

Defined in GHC.Types.ForeignCall

Outputable CCallSpec Source # 
Instance details

Defined in GHC.Types.ForeignCall

Outputable CExportSpec Source # 
Instance details

Defined in GHC.Types.ForeignCall

Outputable CType Source # 
Instance details

Defined in GHC.Types.ForeignCall

Outputable ForeignCall Source # 
Instance details

Defined in GHC.Types.ForeignCall

Outputable Header Source # 
Instance details

Defined in GHC.Types.ForeignCall

Outputable Safety Source # 
Instance details

Defined in GHC.Types.ForeignCall

Outputable CafInfo Source # 
Instance details

Defined in GHC.Types.Id.Info

Outputable IdDetails Source # 
Instance details

Defined in GHC.Types.Id.Info

Outputable IdInfo Source # 
Instance details

Defined in GHC.Core.Ppr

Outputable LevityInfo Source # 
Instance details

Defined in GHC.Types.Id.Info

Outputable RecSelParent Source # 
Instance details

Defined in GHC.Types.Id.Info

Outputable TickBoxOp Source # 
Instance details

Defined in GHC.Types.Id.Info

Outputable Literal Source # 
Instance details

Defined in GHC.Types.Literal

Outputable Name Source # 
Instance details

Defined in GHC.Types.Name

Outputable OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Outputable GlobalRdrElt Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable ImportSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable LocalRdrEnv Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable Parent Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable SlotTy Source # 
Instance details

Defined in GHC.Types.RepType

Outputable RealSrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable UnhelpfulSpanReason Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable Unique Source # 
Instance details

Defined in GHC.Types.Unique

Outputable AnonArgFlag Source # 
Instance details

Defined in GHC.Types.Var

Outputable ArgFlag Source # 
Instance details

Defined in GHC.Types.Var

Outputable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc Source #

pprPrec :: Rational -> Var -> SDoc Source #

Outputable InScopeSet Source # 
Instance details

Defined in GHC.Types.Var.Env

Outputable PackageId Source # 
Instance details

Defined in GHC.Unit.Info

Outputable PackageName Source # 
Instance details

Defined in GHC.Unit.Info

Outputable ModLocation Source # 
Instance details

Defined in GHC.Unit.Module.Location

Outputable ModuleName Source # 
Instance details

Defined in GHC.Unit.Module.Name

Outputable UnitPprInfo Source # 
Instance details

Defined in GHC.Unit.Ppr

Outputable ModuleOrigin Source # 
Instance details

Defined in GHC.Unit.State

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

Outputable Unit Source # 
Instance details

Defined in GHC.Unit.Types

Outputable UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Outputable PprStyle Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable QualifyName Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Serialized Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Extension Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Ordering Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Integer Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable () Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: () -> SDoc Source #

pprPrec :: Rational -> () -> SDoc Source #

Outputable Bool Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Char Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Double Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Float Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable Int Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int -> SDoc Source #

pprPrec :: Rational -> Int -> SDoc Source #

Outputable Word Source # 
Instance details

Defined in GHC.Utils.Outputable

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

Defined in GHC.Utils.Outputable

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

Defined in GHC.Utils.Outputable

Methods

ppr :: SCC a -> SDoc Source #

pprPrec :: Rational -> SCC a -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: IntMap elt -> SDoc Source #

pprPrec :: Rational -> IntMap elt -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: Set a -> SDoc Source #

pprPrec :: Rational -> Set a -> SDoc Source #

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

Defined in GHC.ByteCode.Instr

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

Defined in GHC.Cmm

Outputable (GenCmmStatics a) Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

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

Defined in GHC.Cmm

Methods

ppr :: ListGraph instr -> SDoc Source #

pprPrec :: Rational -> ListGraph instr -> SDoc Source #

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

Defined in GHC.Cmm.Dataflow.Label

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

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

ppr :: InstrSR instr -> SDoc Source #

pprPrec :: Rational -> InstrSR instr -> SDoc Source #

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

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

ppr :: LiveInstr instr -> SDoc Source #

pprPrec :: Rational -> LiveInstr instr -> SDoc Source #

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

Defined in GHC.Core.Ppr

Methods

ppr :: Bind b -> SDoc Source #

pprPrec :: Rational -> Bind b -> SDoc Source #

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

Defined in GHC.Core.Ppr

Methods

ppr :: Expr b -> SDoc Source #

pprPrec :: Rational -> Expr b -> SDoc Source #

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

Defined in GHC.Core

Outputable id => Outputable (Tickish id) Source # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: Tickish id -> SDoc Source #

pprPrec :: Rational -> Tickish id -> SDoc Source #

Outputable (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiom br -> SDoc Source #

pprPrec :: Rational -> CoAxiom br -> SDoc Source #

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

Defined in GHC.Core.Map

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

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc Source #

pprPrec :: Rational -> Scaled a -> SDoc Source #

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

Defined in GHC.Core.Unify

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

Defined in GHC.Data.Bag

Methods

ppr :: Bag a -> SDoc Source #

pprPrec :: Rational -> Bag a -> SDoc Source #

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

Defined in GHC.Data.BooleanFormula

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

Defined in GHC.Data.Graph.Directed

Methods

ppr :: Graph node -> SDoc Source #

pprPrec :: Rational -> Graph node -> SDoc Source #

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

Defined in GHC.Data.OrdList

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

Defined in GHC.Data.Pair

Methods

ppr :: Pair a -> SDoc Source #

pprPrec :: Rational -> Pair a -> SDoc Source #

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

Methods

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

pprPrec :: Rational -> Sig (GhcPass p) -> SDoc Source #

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Outputable (FamilyInfo pass) Source # 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: FamilyInfo pass -> SDoc Source #

pprPrec :: Rational -> FamilyInfo pass -> SDoc Source #

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

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

Defined in GHC.Hs.Decls

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

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

Defined in GHC.Hs.Expr

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

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

Defined in GHC.Hs.ImpExp

Methods

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

pprPrec :: Rational -> IE (GhcPass p) -> SDoc Source #

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

Defined in GHC.Hs.ImpExp

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

Defined in GHC.Hs.ImpExp

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

Defined in GHC.Hs.Lit

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

Defined in GHC.Hs.Lit

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

Defined in GHC.Hs.Pat

Methods

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

pprPrec :: Rational -> 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

Outputable (FieldOcc pass) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: FieldOcc pass -> SDoc Source #

pprPrec :: Rational -> 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 #

pprPrec :: Rational -> 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

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Type

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

Defined in GHC.HsToCore.PmCheck.Types

Methods

ppr :: Shared a -> SDoc Source #

pprPrec :: Rational -> Shared a -> SDoc Source #

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

Defined in GHC.HsToCore.PmCheck.Types

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

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieAST a -> SDoc Source #

pprPrec :: Rational -> HieAST a -> SDoc Source #

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

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Utils

Outputable (PatBuilder GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

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

Defined in GHC.StgToCmm.Closure

Outputable theta => Outputable (DerivSpec theta) Source # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: DerivSpec theta -> SDoc Source #

pprPrec :: Rational -> DerivSpec theta -> SDoc Source #

Outputable (FunDepEqn a) Source # 
Instance details

Defined in GHC.Tc.Instance.FunDeps

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

Defined in GHC.Tc.Solver.Canonical

OutputableBndrId a => Outputable (InstInfo (GhcPass a)) Source # 
Instance details

Defined in GHC.Tc.Utils.Env

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

Defined in GHC.Tc.Utils.Unify

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

Defined in GHC.Types.Annotations

Methods

ppr :: AnnTarget name -> SDoc Source #

pprPrec :: Rational -> AnnTarget name -> SDoc Source #

Outputable (DefMethSpec ty) Source # 
Instance details

Defined in GHC.Types.Basic

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

Defined in GHC.Types.FieldLabel

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

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc Source #

pprPrec :: Rational -> OccEnv a -> SDoc Source #

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

Defined in GHC.Types.Unique.DSet

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

Defined in GHC.Types.Unique.Set

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

Defined in GHC.Unit.Types

Methods

ppr :: Definite unit -> SDoc Source #

pprPrec :: Rational -> Definite unit -> SDoc Source #

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

Defined in GHC.Unit.Types

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

Defined in GHC.Unit.Types

Methods

ppr :: Indefinite unit -> SDoc Source #

pprPrec :: Rational -> Indefinite unit -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: Maybe a -> SDoc Source #

pprPrec :: Rational -> Maybe a -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: [a] -> SDoc Source #

pprPrec :: Rational -> [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 #

pprPrec :: Rational -> 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 #

pprPrec :: Rational -> Map key elt -> SDoc Source #

Outputable (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

ppr :: CmmNode e x -> SDoc Source #

pprPrec :: Rational -> CmmNode e x -> SDoc Source #

(Outputable statics, Outputable instr) => Outputable (RegAllocStats statics instr) Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Graph.Stats

Methods

ppr :: RegAllocStats statics instr -> SDoc Source #

pprPrec :: Rational -> RegAllocStats statics instr -> 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 #

pprPrec :: Rational -> 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 #

pprPrec :: Rational -> 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 #

pprPrec :: Rational -> ListMap m a -> SDoc Source #

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Binds

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

Just print the original expression (the a).

Instance details

Defined in GHC.Hs.Expr

(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 #

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

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

Defined in GHC.Hs.Expr

Methods

ppr :: ParStmtBlock idL idR -> SDoc Source #

pprPrec :: Rational -> ParStmtBlock idL idR -> SDoc Source #

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

Defined in GHC.Hs.Pat

Methods

ppr :: HsRecField' p arg -> SDoc Source #

pprPrec :: Rational -> HsRecField' p arg -> SDoc Source #

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

Defined in GHC.Hs.Pat

Methods

ppr :: HsRecFields p arg -> SDoc Source #

pprPrec :: Rational -> HsRecFields p arg -> SDoc Source #

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

Defined in GHC.Hs.Type

Methods

ppr :: HsArg tm ty -> SDoc Source #

pprPrec :: Rational -> HsArg tm ty -> SDoc Source #

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

Defined in GHC.Hs.Type

Methods

ppr :: HsConDetails arg rec -> SDoc Source #

pprPrec :: Rational -> HsConDetails arg rec -> SDoc Source #

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

Defined in GHC.Hs.Type

Outputable a => Outputable (HsScaled pass a) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsScaled pass a -> SDoc Source #

pprPrec :: Rational -> HsScaled pass a -> SDoc Source #

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

Defined in GHC.Hs.Type

Methods

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

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

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

Defined in GHC.Hs.Type

(Outputable l, Outputable e) => Outputable (GenLocated l 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 #

pprPrec :: Rational -> 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 #

pprPrec :: Rational -> UniqFM key a -> 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

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

Defined in GHC.Types.Var

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

Defined in GHC.Utils.Outputable

Methods

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

pprPrec :: Rational -> (a, b) -> SDoc Source #

(Outputable d, Outputable info, Outputable i) => Outputable (GenCmmDecl d info i) Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

Methods

ppr :: GenCmmDecl d info i -> SDoc Source #

pprPrec :: Rational -> GenCmmDecl d info i -> SDoc Source #

Outputable (Block CmmNode C C) Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable (Block CmmNode C O) Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable (Block CmmNode O C) Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable (Block CmmNode O O) Source # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable (Graph CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Ppr

(OutputableBndrId pl, OutputableBndrId pr, 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 #

pprPrec :: Rational -> StmtLR (GhcPass pl) (GhcPass pr) body -> 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 #

pprPrec :: Rational -> (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 #

pprPrec :: Rational -> (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 #

pprPrec :: Rational -> (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 #

pprPrec :: Rational -> (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 #

pprPrec :: Rational -> (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 HsIPName Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndr BinderInfo Source # 
Instance details

Defined in GHC.Stg.Lift.Analysis

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

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

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

Defined in GHC.Hs.Type

Pretty printing combinators

data SDoc Source #

Represents a pretty-printable document.

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

Instances

Instances details
IsString SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

Outputable SDoc Source # 
Instance details

Defined in GHC.Utils.Outputable

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.

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'

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

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.

printForC :: DynFlags -> Handle -> SDoc -> IO () Source #

Like printSDocLn but specialized with LeftMode and PprCode CStyle. This is typically used to output C-- code.

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)

data PprStyle Source #

Instances

Instances details
Outputable PprStyle Source # 
Instance details

Defined in GHC.Utils.Outputable

data CodeStyle Source #

Constructors

CStyle 
AsmStyle 

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

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

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

Error handling and debugging utilities

pprPanic :: HasCallStack => String -> SDoc -> a Source #

Throw an exception saying "bug in GHC"

pprSorry :: String -> SDoc -> a Source #

Throw an exception saying "this isn't finished yet"

assertPprPanic :: HasCallStack => String -> Int -> SDoc -> a Source #

Panic with an assertion failure, recording the given file and line number. Should typically be accessed with the ASSERT family of macros

pprPgmError :: String -> SDoc -> a Source #

Throw an exception saying "bug in pgm being compiled" (used for unusual program errors)

pprTrace :: String -> SDoc -> a -> a Source #

If debug output is on, show some SDoc on the screen

pprTraceDebug :: String -> SDoc -> a -> a Source #

pprTraceWith :: String -> (a -> SDoc) -> a -> a Source #

pprTraceWith desc f x is equivalent to pprTrace desc (f x) x. This allows you to print details from the returned value as well as from ambient variables.

pprTraceIt :: Outputable a => String -> a -> a Source #

pprTraceIt desc x is equivalent to pprTrace desc (ppr x) x

warnPprTrace :: HasCallStack => Bool -> String -> Int -> SDoc -> a -> a Source #

Just warn about an assertion failure, recording the given file and line number. Should typically be accessed with the WARN macros

pprSTrace :: HasCallStack => SDoc -> a -> a Source #

If debug output is on, show some SDoc on the screen along with a call stack when available.

pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a Source #

pprTraceException desc x action runs action, printing a message if it throws an exception.

pprTraceWithFlags :: DynFlags -> String -> SDoc -> a -> a Source #

If debug output is on, show some SDoc on the screen

trace :: String -> a -> a Source #

The trace function outputs the trace message given as its first argument, before returning the second argument as its result.

For example, this returns the value of f x but first outputs the message.

>>> let x = 123; f = show
>>> trace ("calling f with x = " ++ show x) (f x)
"calling f with x = 123
123"

The trace function should only be used for debugging, or for monitoring execution. The function is not referentially transparent: its type indicates that it is a pure function but it has the side effect of outputting the trace message.

pgmError :: String -> a Source #

Panics and asserts.

panic :: String -> a Source #

Panics and asserts.

sorry :: String -> a Source #

Panics and asserts.

assertPanic :: String -> Int -> a Source #

Throw a failed assertion exception for a given filename and line number.

pprDebugAndThen :: DynFlags -> (String -> a) -> SDoc -> SDoc -> a Source #