ghc-9.2.0.20210422: 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

Methods

ppr :: a -> SDoc Source #

Instances

Instances details
Outputable Fingerprint # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Fingerprint -> SDoc Source #

Outputable Int32 # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int32 -> SDoc Source #

Outputable Int64 # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int64 -> SDoc Source #

Outputable Word16 # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word16 -> SDoc Source #

Outputable Word32 # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word32 -> SDoc Source #

Outputable Word64 # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word64 -> SDoc Source #

Outputable IntSet # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: IntSet -> SDoc Source #

Outputable CoreModule # 
Instance details

Defined in GHC

Methods

ppr :: CoreModule -> SDoc Source #

Outputable PrimCall # 
Instance details

Defined in GHC.Builtin.PrimOps

Methods

ppr :: PrimCall -> SDoc Source #

Outputable PrimOp # 
Instance details

Defined in GHC.Builtin.PrimOps

Methods

ppr :: PrimOp -> SDoc Source #

Outputable BCInstr # 
Instance details

Defined in GHC.ByteCode.Instr

Methods

ppr :: BCInstr -> SDoc Source #

Outputable LocalLabel # 
Instance details

Defined in GHC.ByteCode.Instr

Methods

ppr :: LocalLabel -> SDoc Source #

Outputable ByteOff # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: ByteOff -> SDoc Source #

Outputable CgBreakInfo # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: CgBreakInfo -> SDoc Source #

Outputable CompiledByteCode # 
Instance details

Defined in GHC.ByteCode.Types

Outputable RegBitmap # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: RegBitmap -> SDoc Source #

Outputable TupleInfo # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: TupleInfo -> SDoc Source #

Outputable UnlinkedBCO # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: UnlinkedBCO -> SDoc Source #

Outputable WordOff # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: WordOff -> SDoc Source #

Outputable CmmStackInfo # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable CmmStatic # 
Instance details

Defined in GHC.Cmm

Methods

ppr :: CmmStatic -> SDoc Source #

Outputable ConInfoTableLocation # 
Instance details

Defined in GHC.Cmm.CLabel

Outputable ForeignLabelSource # 
Instance details

Defined in GHC.Cmm.CLabel

Outputable ParamLocation # 
Instance details

Defined in GHC.Cmm.CallConv

Outputable Label # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: Label -> SDoc Source #

Outputable LabelSet # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: LabelSet -> SDoc Source #

Outputable Area # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

ppr :: Area -> SDoc Source #

Outputable CmmLit # 
Instance details

Defined in GHC.Cmm.Expr

Methods

ppr :: CmmLit -> SDoc Source #

Outputable CmmReg # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

ppr :: CmmReg -> SDoc Source #

Outputable GlobalReg # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

ppr :: GlobalReg -> SDoc Source #

Outputable LocalReg # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

ppr :: LocalReg -> SDoc Source #

Outputable CmmReturnInfo # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable CmmTickScope # 
Instance details

Defined in GHC.Cmm.Node

Outputable Convention # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

ppr :: Convention -> SDoc Source #

Outputable ForeignConvention # 
Instance details

Defined in GHC.Cmm.Ppr

Outputable Status # 
Instance details

Defined in GHC.Cmm.ProcPoint

Methods

ppr :: Status -> SDoc Source #

Outputable CmmType # 
Instance details

Defined in GHC.Cmm.Type

Methods

ppr :: CmmType -> SDoc Source #

Outputable ForeignHint # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

Methods

ppr :: ForeignHint -> SDoc Source #

Outputable Width # 
Instance details

Defined in GHC.Cmm.Type

Methods

ppr :: Width -> SDoc Source #

Outputable CfgEdge # 
Instance details

Defined in GHC.CmmToAsm.CFG

Methods

ppr :: CfgEdge -> SDoc Source #

Outputable EdgeInfo # 
Instance details

Defined in GHC.CmmToAsm.CFG

Methods

ppr :: EdgeInfo -> SDoc Source #

Outputable EdgeWeight # 
Instance details

Defined in GHC.CmmToAsm.CFG

Methods

ppr :: EdgeWeight -> SDoc Source #

Outputable JumpDest # 
Instance details

Defined in GHC.CmmToAsm.PPC.RegInfo

Methods

ppr :: JumpDest -> SDoc Source #

Outputable SpillStats # 
Instance details

Defined in GHC.CmmToAsm.Reg.Graph.Spill

Methods

ppr :: SpillStats -> SDoc Source #

Outputable Loc # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.Base

Methods

ppr :: Loc -> SDoc Source #

Outputable FreeRegs # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.PPC

Methods

ppr :: FreeRegs -> SDoc Source #

Outputable FreeRegs # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.SPARC

Methods

ppr :: FreeRegs -> SDoc Source #

Outputable FreeRegs # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.X86

Methods

ppr :: FreeRegs -> SDoc Source #

Outputable FreeRegs # 
Instance details

Defined in GHC.CmmToAsm.Reg.Linear.X86_64

Methods

ppr :: FreeRegs -> SDoc Source #

Outputable JumpDest # 
Instance details

Defined in GHC.CmmToAsm.SPARC.ShortcutJump

Methods

ppr :: JumpDest -> SDoc Source #

Outputable JumpDest # 
Instance details

Defined in GHC.CmmToAsm.X86.Instr

Methods

ppr :: JumpDest -> SDoc Source #

Outputable AltCon # 
Instance details

Defined in GHC.Core

Methods

ppr :: AltCon -> SDoc Source #

Outputable CoreRule # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: CoreRule -> SDoc Source #

Outputable Unfolding # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: Unfolding -> SDoc Source #

Outputable UnfoldingGuidance # 
Instance details

Defined in GHC.Core.Ppr

Outputable UnfoldingSource # 
Instance details

Defined in GHC.Core.Ppr

Outputable Class # 
Instance details

Defined in GHC.Core.Class

Methods

ppr :: Class -> SDoc Source #

Outputable LiftingContext # 
Instance details

Defined in GHC.Core.Coercion

Outputable CoAxBranch # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxBranch -> SDoc Source #

Outputable CoAxiomRule # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiomRule -> SDoc Source #

Outputable Role # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: Role -> SDoc Source #

Outputable ConLike # 
Instance details

Defined in GHC.Core.ConLike

Methods

ppr :: ConLike -> SDoc Source #

Outputable DataCon # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: DataCon -> SDoc Source #

Outputable EqSpec # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: EqSpec -> SDoc Source #

Outputable HsImplBang # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsImplBang -> SDoc Source #

Outputable HsSrcBang # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsSrcBang -> SDoc Source #

Outputable SrcStrictness # 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcUnpackedness # 
Instance details

Defined in GHC.Core.DataCon

Outputable StrictnessMark # 
Instance details

Defined in GHC.Core.DataCon

Outputable FamInst # 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInst -> SDoc Source #

Outputable FamInstMatch # 
Instance details

Defined in GHC.Core.FamInstEnv

Outputable ClsInst # 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: ClsInst -> SDoc Source #

Outputable FloatBind # 
Instance details

Defined in GHC.Core.Make

Methods

ppr :: FloatBind -> SDoc Source #

Outputable IsSubmult # 
Instance details

Defined in GHC.Core.Multiplicity

Methods

ppr :: IsSubmult -> SDoc Source #

Outputable ArityType #

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 # 
Instance details

Defined in GHC.Core.Opt.CallerCC

Outputable CoreToDo # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: CoreToDo -> SDoc Source #

Outputable FloatOutSwitches # 
Instance details

Defined in GHC.Core.Opt.Monad

Outputable SimplMode # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: SimplMode -> SDoc Source #

Outputable Tick # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: Tick -> SDoc Source #

Outputable FloatSpec # 
Instance details

Defined in GHC.Core.Opt.SetLevels

Methods

ppr :: FloatSpec -> SDoc Source #

Outputable Level # 
Instance details

Defined in GHC.Core.Opt.SetLevels

Methods

ppr :: Level -> SDoc Source #

Outputable LetFloats # 
Instance details

Defined in GHC.Core.Opt.Simplify.Env

Methods

ppr :: LetFloats -> SDoc Source #

Outputable SimplFloats # 
Instance details

Defined in GHC.Core.Opt.Simplify.Env

Methods

ppr :: SimplFloats -> SDoc Source #

Outputable SimplSR # 
Instance details

Defined in GHC.Core.Opt.Simplify.Env

Methods

ppr :: SimplSR -> SDoc Source #

Outputable ArgInfo # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Methods

ppr :: ArgInfo -> SDoc Source #

Outputable ArgSpec # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Methods

ppr :: ArgSpec -> SDoc Source #

Outputable DupFlag # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Methods

ppr :: DupFlag -> SDoc Source #

Outputable SimplCont # 
Instance details

Defined in GHC.Core.Opt.Simplify.Utils

Methods

ppr :: SimplCont -> SDoc Source #

Outputable PatSyn # 
Instance details

Defined in GHC.Core.PatSyn

Methods

ppr :: PatSyn -> SDoc Source #

Outputable EqRel # 
Instance details

Defined in GHC.Core.Predicate

Methods

ppr :: EqRel -> SDoc Source #

Outputable CoreStats # 
Instance details

Defined in GHC.Core.Stats

Methods

ppr :: CoreStats -> SDoc Source #

Outputable Subst # 
Instance details

Defined in GHC.Core.Subst

Methods

ppr :: Subst -> SDoc Source #

Outputable Coercion # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Coercion -> SDoc Source #

Outputable CoercionHole # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable MCoercion # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: MCoercion -> SDoc Source #

Outputable TyCoBinder # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyCoBinder -> SDoc Source #

Outputable TyLit # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyLit -> SDoc Source #

Outputable Type # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc Source #

Outputable UnivCoProvenance # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable TCvSubst # 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: TCvSubst -> SDoc Source #

Outputable AlgTyConFlav # 
Instance details

Defined in GHC.Core.TyCon

Outputable FamTyConFlav # 
Instance details

Defined in GHC.Core.TyCon

Outputable PrimElemRep # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: PrimElemRep -> SDoc Source #

Outputable PrimRep # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: PrimRep -> SDoc Source #

Outputable TyCon # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyCon -> SDoc Source #

Outputable TyConBndrVis # 
Instance details

Defined in GHC.Core.TyCon

Outputable TyConFlavour # 
Instance details

Defined in GHC.Core.TyCon

Outputable ArgSummary # 
Instance details

Defined in GHC.Core.Unfold

Methods

ppr :: ArgSummary -> SDoc Source #

Outputable CallCtxt # 
Instance details

Defined in GHC.Core.Unfold

Methods

ppr :: CallCtxt -> SDoc Source #

Outputable MaybeApartReason # 
Instance details

Defined in GHC.Core.Unify

Outputable Usage # 
Instance details

Defined in GHC.Core.UsageEnv

Methods

ppr :: Usage -> SDoc Source #

Outputable UsageEnv # 
Instance details

Defined in GHC.Core.UsageEnv

Methods

ppr :: UsageEnv -> SDoc Source #

Outputable FastString # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: FastString -> SDoc Source #

Outputable LexicalFastString # 
Instance details

Defined in GHC.Utils.Outputable

Outputable NonDetFastString # 
Instance details

Defined in GHC.Utils.Outputable

Outputable EdgeType # 
Instance details

Defined in GHC.Data.Graph.Directed

Methods

ppr :: EdgeType -> SDoc Source #

Outputable UnVarGraph # 
Instance details

Defined in GHC.Data.Graph.UnVar

Methods

ppr :: UnVarGraph -> SDoc Source #

Outputable UnVarSet # 
Instance details

Defined in GHC.Data.Graph.UnVar

Methods

ppr :: UnVarSet -> SDoc Source #

Outputable HsComponentId # 
Instance details

Defined in GHC.Driver.Backpack.Syntax

Outputable WarnReason # 
Instance details

Defined in GHC.Driver.CmdLine

Methods

ppr :: WarnReason -> SDoc Source #

Outputable Language # 
Instance details

Defined in GHC.Driver.Flags

Methods

ppr :: Language -> SDoc Source #

Outputable WarnReason # 
Instance details

Defined in GHC.Driver.Flags

Methods

ppr :: WarnReason -> SDoc Source #

Outputable Phase # 
Instance details

Defined in GHC.Driver.Phases

Methods

ppr :: Phase -> SDoc Source #

Outputable PhasePlus # 
Instance details

Defined in GHC.Driver.Pipeline.Monad

Methods

ppr :: PhasePlus -> SDoc Source #

Outputable PluginRecompile # 
Instance details

Defined in GHC.Driver.Plugins

Outputable GhcMode # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: GhcMode -> SDoc Source #

Outputable ModRenaming # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: ModRenaming -> SDoc Source #

Outputable PackageArg # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageArg -> SDoc Source #

Outputable PackageFlag # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageFlag -> SDoc Source #

Outputable HsModule # 
Instance details

Defined in GHC.Hs

Methods

ppr :: HsModule -> SDoc Source #

Outputable XViaStrategyPs # 
Instance details

Defined in GHC.Hs.Decls

Outputable ArgDocMap # 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: ArgDocMap -> SDoc Source #

Outputable DeclDocMap # 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: DeclDocMap -> SDoc Source #

Outputable HsDocString # 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: HsDocString -> SDoc Source #

Outputable GrhsAnn # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: GrhsAnn -> SDoc Source #

Outputable PendingRnSplice # 
Instance details

Defined in GHC.Hs.Expr

Outputable PendingTcSplice # 
Instance details

Defined in GHC.Hs.Expr

Outputable SyntaxExprRn # 
Instance details

Defined in GHC.Hs.Expr

Outputable SyntaxExprTc # 
Instance details

Defined in GHC.Hs.Expr

Outputable DsMatchContext # 
Instance details

Defined in GHC.HsToCore.Monad

Outputable EquationInfo # 
Instance details

Defined in GHC.HsToCore.Monad

Outputable PhiCt # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver

Methods

ppr :: PhiCt -> SDoc Source #

Outputable BotInfo # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: BotInfo -> SDoc Source #

Outputable Nabla # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: Nabla -> SDoc Source #

Outputable Nablas # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: Nablas -> SDoc Source #

Outputable PmAltCon # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltCon -> SDoc Source #

Outputable PmAltConApp # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltConApp -> SDoc Source #

Outputable PmAltConSet # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltConSet -> SDoc Source #

Outputable PmEquality # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmEquality -> SDoc Source #

Outputable PmLit # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmLit -> SDoc Source #

Outputable PmLitValue # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmLitValue -> SDoc Source #

Outputable ResidualCompleteMatches # 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Outputable TmState #

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: TmState -> SDoc Source #

Outputable TyState #

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: TyState -> SDoc Source #

Outputable VarInfo #

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: VarInfo -> SDoc Source #

Outputable GrdVec #

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 # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmEmptyCase -> SDoc Source #

Outputable PmGrd #

Should not be user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGrd -> SDoc Source #

Outputable Precision # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: Precision -> SDoc Source #

Outputable RedSets # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: RedSets -> SDoc Source #

Outputable SrcInfo # 
Instance details

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: SrcInfo -> SDoc Source #

Outputable BindType # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: BindType -> SDoc Source #

Outputable ContextInfo # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: ContextInfo -> SDoc Source #

Outputable DeclType # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: DeclType -> SDoc Source #

Outputable EvBindDeps # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: EvBindDeps -> SDoc Source #

Outputable EvVarSource # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: EvVarSource -> SDoc Source #

Outputable HieName # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieName -> SDoc Source #

Outputable IEType # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: IEType -> SDoc Source #

Outputable NodeAnnotation # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable NodeOrigin # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: NodeOrigin -> SDoc Source #

Outputable RecFieldContext # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable Scope # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: Scope -> SDoc Source #

Outputable TyVarScope # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: TyVarScope -> SDoc Source #

Outputable IfaceAT # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceAT -> SDoc Source #

Outputable IfaceAnnotation # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceClassOp # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceClsInst # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceCompleteMatch # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceConAlt # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceConAlt -> SDoc Source #

Outputable IfaceDecl # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceDecl -> SDoc Source #

Outputable IfaceExpr # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceExpr -> SDoc Source #

Outputable IfaceFamInst # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceIdDetails # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceInfoItem # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceJoinInfo # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceLFInfo # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceLFInfo -> SDoc Source #

Outputable IfaceRule # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceRule -> SDoc Source #

Outputable IfaceTyConParent # 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceUnfolding # 
Instance details

Defined in GHC.Iface.Syntax

Outputable ShowHowMuch # 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: ShowHowMuch -> SDoc Source #

Outputable IfaceAppArgs # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceBndr # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceBndr -> SDoc Source #

Outputable IfaceCoercion # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceOneShot # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyCon # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceTyCon -> SDoc Source #

Outputable IfaceTyConInfo # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyConSort # 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyLit # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceTyLit -> SDoc Source #

Outputable IfaceType # 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceType -> SDoc Source #

Outputable Linkable # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Linkable -> SDoc Source #

Outputable SptEntry # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: SptEntry -> SDoc Source #

Outputable Unlinked # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Unlinked -> SDoc Source #

Outputable MetaId # 
Instance details

Defined in GHC.Llvm.MetaData

Methods

ppr :: MetaId -> SDoc Source #

Outputable LlvmCallConvention # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmCastOp # 
Instance details

Defined in GHC.Llvm.Types

Methods

ppr :: LlvmCastOp -> SDoc Source #

Outputable LlvmCmpOp # 
Instance details

Defined in GHC.Llvm.Types

Methods

ppr :: LlvmCmpOp -> SDoc Source #

Outputable LlvmFuncAttr # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmFunctionDecl # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmLinkageType # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmMachOp # 
Instance details

Defined in GHC.Llvm.Types

Methods

ppr :: LlvmMachOp -> SDoc Source #

Outputable LlvmParamAttr # 
Instance details

Defined in GHC.Llvm.Types

Outputable LlvmType # 
Instance details

Defined in GHC.Llvm.Types

Methods

ppr :: LlvmType -> SDoc Source #

Outputable AddEpAnn # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AddEpAnn -> SDoc Source #

Outputable Anchor # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: Anchor -> SDoc Source #

Outputable AnchorOperation # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnContext # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnContext -> SDoc Source #

Outputable AnnKeywordId # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnList # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnList -> SDoc Source #

Outputable AnnListItem # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnListItem -> SDoc Source #

Outputable AnnPragma # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnPragma -> SDoc Source #

Outputable AnnSortKey # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnSortKey -> SDoc Source #

Outputable DeltaPos # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: DeltaPos -> SDoc Source #

Outputable EpAnnComments # 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpaComment # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaComment -> SDoc Source #

Outputable EpaLocation # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaLocation -> SDoc Source #

Outputable IsUnicodeSyntax # 
Instance details

Defined in GHC.Parser.Annotation

Outputable NameAdornment # 
Instance details

Defined in GHC.Parser.Annotation

Outputable NameAnn # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NameAnn -> SDoc Source #

Outputable TrailingAnn # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: TrailingAnn -> SDoc Source #

Outputable Token # 
Instance details

Defined in GHC.Parser.Lexer

Methods

ppr :: Token -> SDoc Source #

Outputable DataConBuilder # 
Instance details

Defined in GHC.Parser.Types

Outputable RealReg # 
Instance details

Defined in GHC.Platform.Reg

Methods

ppr :: RealReg -> SDoc Source #

Outputable Reg #

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 # 
Instance details

Defined in GHC.Platform.Reg

Methods

ppr :: VirtualReg -> SDoc Source #

Outputable RegClass # 
Instance details

Defined in GHC.Platform.Reg.Class

Methods

ppr :: RegClass -> SDoc Source #

Outputable ChildLookupResult # 
Instance details

Defined in GHC.Rename.Env

Outputable HsSigCtxt # 
Instance details

Defined in GHC.Rename.Env

Methods

ppr :: HsSigCtxt -> SDoc Source #

Outputable WarnUnusedForalls # 
Instance details

Defined in GHC.Rename.HsType

Outputable InteractiveImport # 
Instance details

Defined in GHC.Runtime.Context

Outputable GetDocsFailure # 
Instance details

Defined in GHC.Runtime.Eval

Outputable Term # 
Instance details

Defined in GHC.Runtime.Heap.Inspect

Methods

ppr :: Term -> SDoc Source #

Outputable ClosureTypeInfo # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Outputable SMRep # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Methods

ppr :: SMRep -> SDoc Source #

Outputable StgHalfWord # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Methods

ppr :: StgHalfWord -> SDoc Source #

Outputable StgWord # 
Instance details

Defined in GHC.Runtime.Heap.Layout

Methods

ppr :: StgWord -> SDoc Source #

Outputable BinderInfo # 
Instance details

Defined in GHC.Stg.Lift.Analysis

Methods

ppr :: BinderInfo -> SDoc Source #

Outputable Skeleton # 
Instance details

Defined in GHC.Stg.Lift.Analysis

Methods

ppr :: Skeleton -> SDoc Source #

Outputable FloatLang # 
Instance details

Defined in GHC.Stg.Lift.Monad

Methods

ppr :: FloatLang -> SDoc Source #

Outputable AltType # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: AltType -> SDoc Source #

Outputable ConstructorNumber # 
Instance details

Defined in GHC.Stg.Syntax

Outputable NoExtFieldSilent # 
Instance details

Defined in GHC.Stg.Syntax

Outputable StgArg # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: StgArg -> SDoc Source #

Outputable UpdateFlag # 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: UpdateFlag -> SDoc Source #

Outputable ArgRep # 
Instance details

Defined in GHC.StgToCmm.ArgRep

Methods

ppr :: ArgRep -> SDoc Source #

Outputable Sequel # 
Instance details

Defined in GHC.StgToCmm.Monad

Methods

ppr :: Sequel -> SDoc Source #

Outputable ArgDescr # 
Instance details

Defined in GHC.StgToCmm.Types

Methods

ppr :: ArgDescr -> SDoc Source #

Outputable LambdaFormInfo # 
Instance details

Defined in GHC.StgToCmm.Types

Outputable StandardFormInfo # 
Instance details

Defined in GHC.StgToCmm.Types

Outputable DerivContext # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable DerivEnv # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: DerivEnv -> SDoc Source #

Outputable DerivInstTys # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable DerivSpecMechanism # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Outputable PredOrigin # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: PredOrigin -> SDoc Source #

Outputable ThetaOrigin # 
Instance details

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: ThetaOrigin -> SDoc Source #

Outputable HoleFit # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

ppr :: HoleFit -> SDoc Source #

Outputable HoleFitCandidate # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Outputable TypedHole # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

ppr :: TypedHole -> SDoc Source #

Outputable AppCtxt # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: AppCtxt -> SDoc Source #

Outputable HoleMode # 
Instance details

Defined in GHC.Tc.Gen.HsType

Methods

ppr :: HoleMode -> SDoc Source #

Outputable SAKS_or_CUSK # 
Instance details

Defined in GHC.Tc.Gen.HsType

Outputable LetBndrSpec # 
Instance details

Defined in GHC.Tc.Gen.Pat

Methods

ppr :: LetBndrSpec -> SDoc Source #

Outputable ClsInstResult # 
Instance details

Defined in GHC.Tc.Instance.Class

Outputable InstanceWhat # 
Instance details

Defined in GHC.Tc.Instance.Class

Outputable InferMode # 
Instance details

Defined in GHC.Tc.Solver

Methods

ppr :: InferMode -> SDoc Source #

Outputable UnifyTestResult # 
Instance details

Defined in GHC.Tc.Solver.Canonical

Outputable EqualCtList # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: EqualCtList -> SDoc Source #

Outputable InertCans # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: InertCans -> SDoc Source #

Outputable InertSet # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: InertSet -> SDoc Source #

Outputable WorkList # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: WorkList -> SDoc Source #

Outputable IdBindingInfo # 
Instance details

Defined in GHC.Tc.Types

Outputable PromotionErr # 
Instance details

Defined in GHC.Tc.Types

Outputable TcBinder # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcBinder -> SDoc Source #

Outputable TcIdSigInfo # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInfo -> SDoc Source #

Outputable TcIdSigInst # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInst -> SDoc Source #

Outputable TcPatSynInfo # 
Instance details

Defined in GHC.Tc.Types

Outputable TcSigInfo # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcSigInfo -> SDoc Source #

Outputable TcTyThing # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcTyThing -> SDoc Source #

Outputable ThStage # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: ThStage -> SDoc Source #

Outputable WhereFrom # 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: WhereFrom -> SDoc Source #

Outputable CanEqLHS # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CanEqLHS -> SDoc Source #

Outputable Ct # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Ct -> SDoc Source #

Outputable CtEvidence # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CtEvidence -> SDoc Source #

Outputable CtFlavour # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CtFlavour -> SDoc Source #

Outputable CtIrredStatus # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable HasGivenEqs # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: HasGivenEqs -> SDoc Source #

Outputable Hole # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Hole -> SDoc Source #

Outputable HoleSort # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: HoleSort -> SDoc Source #

Outputable ImplicStatus # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable Implication # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Implication -> SDoc Source #

Outputable QCInst # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: QCInst -> SDoc Source #

Outputable SubGoalDepth # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable TcEvDest # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: TcEvDest -> SDoc Source #

Outputable WantedConstraints # 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable EvBind # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBind -> SDoc Source #

Outputable EvBindMap # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindMap -> SDoc Source #

Outputable EvBindsVar # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindsVar -> SDoc Source #

Outputable EvCallStack # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvCallStack -> SDoc Source #

Outputable EvTerm # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTerm -> SDoc Source #

Outputable EvTypeable # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTypeable -> SDoc Source #

Outputable HoleExprRef # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HoleExprRef -> SDoc Source #

Outputable HsWrapper # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HsWrapper -> SDoc Source #

Outputable TcEvBinds # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: TcEvBinds -> SDoc Source #

Outputable CtOrigin # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: CtOrigin -> SDoc Source #

Outputable SkolemInfo # 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: SkolemInfo -> SDoc Source #

Outputable IsExtraConstraint # 
Instance details

Defined in GHC.Tc.Utils.Monad

Outputable CandidatesQTvs # 
Instance details

Defined in GHC.Tc.Utils.TcMType

Outputable ExpType # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: ExpType -> SDoc Source #

Outputable InferResult # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: InferResult -> SDoc Source #

Outputable MetaDetails # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: MetaDetails -> SDoc Source #

Outputable MetaInfo # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: MetaInfo -> SDoc Source #

Outputable TcLevel # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: TcLevel -> SDoc Source #

Outputable TcTyVarDetails # 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable AreTypeFamiliesOK # 
Instance details

Defined in GHC.Tc.Utils.Unify

Outputable CheckTyEqResult # 
Instance details

Defined in GHC.Tc.Utils.Unify

Outputable ZonkEnv # 
Instance details

Defined in GHC.Tc.Utils.Zonk

Methods

ppr :: ZonkEnv -> SDoc Source #

Outputable Rank # 
Instance details

Defined in GHC.Tc.Validity

Methods

ppr :: Rank -> SDoc Source #

Outputable Annotation # 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: Annotation -> SDoc Source #

Outputable AvailInfo # 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: AvailInfo -> SDoc Source #

Outputable GreName # 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: GreName -> SDoc Source #

Outputable Activation # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Activation -> SDoc Source #

Outputable Alignment # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Alignment -> SDoc Source #

Outputable Boxity # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Boxity -> SDoc Source #

Outputable CompilerPhase # 
Instance details

Defined in GHC.Types.Basic

Outputable FunctionOrData # 
Instance details

Defined in GHC.Types.Basic

Outputable InlinePragma # 
Instance details

Defined in GHC.Types.Basic

Outputable InlineSpec # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: InlineSpec -> SDoc Source #

Outputable IntWithInf # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: IntWithInf -> SDoc Source #

Outputable LeftOrRight # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc Source #

Outputable OccInfo # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OccInfo -> SDoc Source #

Outputable OneShotInfo # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OneShotInfo -> SDoc Source #

Outputable Origin # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Origin -> SDoc Source #

Outputable OverlapFlag # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapFlag -> SDoc Source #

Outputable OverlapMode # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapMode -> SDoc Source #

Outputable PromotionFlag # 
Instance details

Defined in GHC.Types.Basic

Outputable RecFlag # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: RecFlag -> SDoc Source #

Outputable RuleMatchInfo # 
Instance details

Defined in GHC.Types.Basic

Outputable SuccessFlag # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SuccessFlag -> SDoc Source #

Outputable SwapFlag # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SwapFlag -> SDoc Source #

Outputable TailCallInfo # 
Instance details

Defined in GHC.Types.Basic

Outputable TopLevelFlag # 
Instance details

Defined in GHC.Types.Basic

Outputable TupleSort # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TupleSort -> SDoc Source #

Outputable TypeOrKind # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TypeOrKind -> SDoc Source #

Outputable CompleteMatch # 
Instance details

Defined in GHC.Types.CompleteMatch

Outputable CostCentre # 
Instance details

Defined in GHC.Types.CostCentre

Methods

ppr :: CostCentre -> SDoc Source #

Outputable CostCentreStack # 
Instance details

Defined in GHC.Types.CostCentre

Outputable Cpr #

BNF: ``` cpr ::= '' -- TopCpr | n -- FlatConCpr n | n '(' cpr1 ',' cpr2 ',' ... ')' -- ConCpr n [cpr1,cpr2,...] | b -- BotCpr ``` Examples: * `f x = f x` has denotation 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 #

Only print the CPR result

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprSig -> SDoc Source #

Outputable CprType # 
Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprType -> SDoc Source #

Outputable Card #

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

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Card -> SDoc Source #

Outputable Demand #

See Note [Demand notation]

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Demand -> SDoc Source #

Outputable Divergence # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Divergence -> SDoc Source #

Outputable DmdType # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: DmdType -> SDoc Source #

Outputable StrictSig # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: StrictSig -> SDoc Source #

Outputable SubDemand #

See Note [Demand notation]

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: SubDemand -> SDoc Source #

Outputable TypeShape # 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: TypeShape -> SDoc Source #

Outputable DuplicateRecordFields # 
Instance details

Defined in GHC.Types.FieldLabel

Outputable FieldLabel # 
Instance details

Defined in GHC.Types.FieldLabel

Methods

ppr :: FieldLabel -> SDoc Source #

Outputable FieldSelectors # 
Instance details

Defined in GHC.Types.FieldLabel

Outputable Fixity # 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: Fixity -> SDoc Source #

Outputable FixityDirection # 
Instance details

Defined in GHC.Types.Fixity

Outputable LexicalFixity # 
Instance details

Defined in GHC.Types.Fixity

Outputable FixItem # 
Instance details

Defined in GHC.Types.Fixity.Env

Methods

ppr :: FixItem -> SDoc Source #

Outputable CCallConv # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CCallConv -> SDoc Source #

Outputable CCallSpec # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CCallSpec -> SDoc Source #

Outputable CExportSpec # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CExportSpec -> SDoc Source #

Outputable CType # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CType -> SDoc Source #

Outputable ForeignCall # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: ForeignCall -> SDoc Source #

Outputable Header # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: Header -> SDoc Source #

Outputable Safety # 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: Safety -> SDoc Source #

Outputable CafInfo # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: CafInfo -> SDoc Source #

Outputable IdDetails # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: IdDetails -> SDoc Source #

Outputable IdInfo # 
Instance details

Defined in GHC.Core.Ppr

Methods

ppr :: IdInfo -> SDoc Source #

Outputable LevityInfo # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: LevityInfo -> SDoc Source #

Outputable RecSelParent # 
Instance details

Defined in GHC.Types.Id.Info

Outputable TickBoxOp # 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: TickBoxOp -> SDoc Source #

Outputable Literal # 
Instance details

Defined in GHC.Types.Literal

Methods

ppr :: Literal -> SDoc Source #

Outputable Name # 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc Source #

Outputable OccName # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc Source #

Outputable GlobalRdrElt # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable ImportSpec # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: ImportSpec -> SDoc Source #

Outputable LocalRdrEnv # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: LocalRdrEnv -> SDoc Source #

Outputable Parent # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: Parent -> SDoc Source #

Outputable RdrName # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc Source #

Outputable SlotTy # 
Instance details

Defined in GHC.Types.RepType

Methods

ppr :: SlotTy -> SDoc Source #

Outputable IfaceTrustInfo # 
Instance details

Defined in GHC.Types.SafeHaskell

Outputable SafeHaskellMode # 
Instance details

Defined in GHC.Types.SafeHaskell

Outputable FractionalLit # 
Instance details

Defined in GHC.Types.SourceText

Outputable IntegralLit # 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: IntegralLit -> SDoc Source #

Outputable SourceText # 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: SourceText -> SDoc Source #

Outputable StringLiteral # 
Instance details

Defined in GHC.Types.SourceText

Outputable RealSrcLoc # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcLoc -> SDoc Source #

Outputable RealSrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc Source #

Outputable SrcLoc # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc Source #

Outputable SrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc Source #

Outputable UnhelpfulSpanReason # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable Target # 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: Target -> SDoc Source #

Outputable TargetId # 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: TargetId -> SDoc Source #

Outputable TyThing # 
Instance details

Defined in GHC.Types.TyThing

Methods

ppr :: TyThing -> SDoc Source #

Outputable Unique # 
Instance details

Defined in GHC.Types.Unique

Methods

ppr :: Unique -> SDoc Source #

Outputable AnonArgFlag # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: AnonArgFlag -> SDoc Source #

Outputable ArgFlag # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: ArgFlag -> SDoc Source #

Outputable Var # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc Source #

Outputable InScopeSet # 
Instance details

Defined in GHC.Types.Var.Env

Methods

ppr :: InScopeSet -> SDoc Source #

Outputable PackageId # 
Instance details

Defined in GHC.Unit.Info

Methods

ppr :: PackageId -> SDoc Source #

Outputable PackageName # 
Instance details

Defined in GHC.Unit.Info

Methods

ppr :: PackageName -> SDoc Source #

Outputable ModuleGraphNode # 
Instance details

Defined in GHC.Unit.Module.Graph

Outputable ModLocation # 
Instance details

Defined in GHC.Unit.Module.Location

Methods

ppr :: ModLocation -> SDoc Source #

Outputable ExtendedModSummary # 
Instance details

Defined in GHC.Unit.Module.ModSummary

Outputable ModSummary # 
Instance details

Defined in GHC.Unit.Module.ModSummary

Methods

ppr :: ModSummary -> SDoc Source #

Outputable ModuleName # 
Instance details

Defined in GHC.Unit.Module.Name

Methods

ppr :: ModuleName -> SDoc Source #

Outputable WarningTxt # 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

ppr :: WarningTxt -> SDoc Source #

Outputable Warnings # 
Instance details

Defined in GHC.Iface.Load

Methods

ppr :: Warnings -> SDoc Source #

Outputable UnitPprInfo # 
Instance details

Defined in GHC.Unit.Ppr

Methods

ppr :: UnitPprInfo -> SDoc Source #

Outputable ModuleOrigin # 
Instance details

Defined in GHC.Unit.State

Outputable UnitErr # 
Instance details

Defined in GHC.Unit.State

Methods

ppr :: UnitErr -> SDoc Source #

Outputable UnusableUnitReason # 
Instance details

Defined in GHC.Unit.State

Outputable InstalledModule # 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedModule # 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedUnit # 
Instance details

Defined in GHC.Unit.Types

Outputable Module # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc Source #

Outputable Unit # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc Source #

Outputable UnitId # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: UnitId -> SDoc Source #

Outputable PprStyle # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: PprStyle -> SDoc Source #

Outputable QualifyName # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: QualifyName -> SDoc Source #

Outputable SDoc # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc Source #

Outputable TcSpecPrag # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: TcSpecPrag -> SDoc Source #

Outputable DocDecl # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: DocDecl -> SDoc Source #

Outputable ForeignExport # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Outputable ForeignImport # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Outputable NewOrData # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: NewOrData -> SDoc Source #

Outputable SpliceDecoration # 
Instance details

Defined in Language.Haskell.Syntax.Expr

Outputable NoExtCon # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

ppr :: NoExtCon -> SDoc Source #

Outputable NoExtField # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

ppr :: NoExtField -> SDoc Source #

Outputable OverLitVal # 
Instance details

Defined in Language.Haskell.Syntax.Lit

Methods

ppr :: OverLitVal -> SDoc Source #

Outputable HsIPName # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsIPName -> SDoc Source #

Outputable HsTyLit # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsTyLit -> SDoc Source #

Outputable Serialized # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Serialized -> SDoc Source #

Outputable Extension # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Extension -> SDoc Source #

Outputable Ordering # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Ordering -> SDoc Source #

Outputable Integer # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Integer -> SDoc Source #

Outputable () # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: () -> SDoc Source #

Outputable Bool # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Bool -> SDoc Source #

Outputable Char # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Char -> SDoc Source #

Outputable Double # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Double -> SDoc Source #

Outputable Float # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Float -> SDoc Source #

Outputable Int # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int -> SDoc Source #

Outputable Word # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: NonEmpty a -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: SCC a -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: IntMap elt -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: Set a -> SDoc Source #

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

Defined in GHC.ByteCode.Instr

Methods

ppr :: ProtoBCO a -> SDoc Source #

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

Defined in GHC.Cmm

Methods

ppr :: GenBasicBlock instr -> SDoc Source #

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

Defined in GHC.Cmm

Methods

ppr :: ListGraph instr -> SDoc Source #

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

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: LabelMap a -> SDoc Source #

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

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

ppr :: InstrSR instr -> SDoc Source #

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

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

ppr :: LiveInstr instr -> SDoc Source #

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

Defined in GHC.Core.Ppr

Methods

ppr :: Alt b -> SDoc Source #

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

Defined in GHC.Core.Ppr

Methods

ppr :: Bind b -> SDoc Source #

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

Defined in GHC.Core.Ppr

Methods

ppr :: Expr b -> SDoc Source #

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

Defined in GHC.Core

Methods

ppr :: TaggedBndr b -> SDoc Source #

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

Defined in GHC.Core.Coercion

Outputable (CoAxiom br) # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiom br -> SDoc Source #

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

Defined in GHC.Core.Map.Expr

Methods

ppr :: CoreMap a -> SDoc Source #

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

Defined in GHC.Core.Map.Type

Methods

ppr :: TypeMapG a -> SDoc Source #

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

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc Source #

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

Defined in GHC.Core.Unify

Methods

ppr :: UnifyResultM a -> SDoc Source #

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

Defined in GHC.Data.Bag

Methods

ppr :: Bag a -> SDoc Source #

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

Defined in GHC.Data.BooleanFormula

Methods

ppr :: BooleanFormula a -> SDoc Source #

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

Defined in GHC.Data.Graph.Directed

Methods

ppr :: Graph node -> SDoc Source #

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

Defined in GHC.Data.OrdList

Methods

ppr :: OrdList a -> SDoc Source #

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

Defined in GHC.Data.Pair

Methods

ppr :: Pair a -> SDoc Source #

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

Defined in GHC.Hs.ImpExp

Methods

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

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

Defined in GHC.Hs.ImpExp

Methods

ppr :: IEWrappedName name -> SDoc Source #

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

Defined in GHC.Hs.ImpExp

Methods

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

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

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: CheckResult a -> SDoc Source #

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

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGRHS p -> SDoc Source #

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

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmGRHSs p -> SDoc Source #

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

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmMatch p -> SDoc Source #

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

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmMatchGroup p -> SDoc Source #

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

Defined in GHC.HsToCore.Pmc.Types

Methods

ppr :: PmPatBind p -> SDoc Source #

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

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieAST a -> SDoc Source #

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

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieASTs a -> SDoc Source #

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

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Types

Methods

ppr :: NodeInfo a -> SDoc Source #

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

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Utils

Methods

ppr :: EvidenceInfo a -> SDoc Source #

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

Defined in GHC.Parser.Annotation

Methods

ppr :: EpAnn a -> SDoc Source #

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

Defined in GHC.Parser.Annotation

Methods

ppr :: SrcSpanAnn' a -> SDoc Source #

Outputable (PatBuilder GhcPs) # 
Instance details

Defined in GHC.Parser.Types

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

Defined in GHC.StgToCmm.Closure

Methods

ppr :: NonVoid a -> SDoc Source #

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

Defined in GHC.Tc.Deriv.Utils

Methods

ppr :: DerivSpec theta -> SDoc Source #

OutputableBndrId (XPass p) => Outputable (EValArg p) # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: EValArg p -> SDoc Source #

OutputableBndrId (XPass p) => Outputable (HsExprArg p) # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: HsExprArg p -> SDoc Source #

Outputable (FunDepEqn a) # 
Instance details

Defined in GHC.Tc.Instance.FunDeps

Methods

ppr :: FunDepEqn a -> SDoc Source #

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

Defined in GHC.Tc.Solver.Canonical

Methods

ppr :: StopOrContinue a -> SDoc Source #

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

Defined in GHC.Tc.Utils.Env

Methods

ppr :: InstInfo (GhcPass a) -> SDoc Source #

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

Defined in GHC.Types.Annotations

Methods

ppr :: AnnTarget name -> SDoc Source #

Outputable (DefMethSpec ty) # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: DefMethSpec ty -> SDoc Source #

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

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc Source #

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

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc Source #

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

Defined in GHC.Core.Ppr

Methods

ppr :: GenTickish pass -> SDoc Source #

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

Defined in GHC.Types.Unique.DSet

Methods

ppr :: UniqDSet a -> SDoc Source #

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

Defined in GHC.Types.Unique.Set

Methods

ppr :: UniqSet a -> SDoc Source #

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

Defined in GHC.Unit.Types

Methods

ppr :: Definite unit -> SDoc Source #

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

Defined in GHC.Unit.Types

Methods

ppr :: GenWithIsBoot a -> SDoc Source #

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

Defined in GHC.Unit.Types

Methods

ppr :: Indefinite unit -> SDoc Source #

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

Defined in GHC.Hs.Binds

Methods

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

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

Defined in GHC.Hs.Binds

Methods

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

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

Defined in GHC.Hs.Binds

Methods

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

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

Defined in GHC.Hs.Binds

Methods

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

Outputable (RecordPatSynField a) # 
Instance details

Defined in Language.Haskell.Syntax.Binds

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

Defined in GHC.Hs.Binds

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Methods

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

Outputable (FamilyInfo pass) # 
Instance details

Defined in Language.Haskell.Syntax.Decls

Methods

ppr :: FamilyInfo pass -> SDoc Source #

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Decls

Methods

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

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

Defined in GHC.Hs.Expr

Methods

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

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

Defined in GHC.Hs.Expr

Methods

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

Outputable (FieldLabelStrings p) # 
Instance details

Defined in Language.Haskell.Syntax.Expr

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

Defined in GHC.Hs.Expr

Methods

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

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

Defined in GHC.Hs.Expr

Methods

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

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

Defined in GHC.Hs.Expr

Methods

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

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

Defined in GHC.Hs.Expr

Methods

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

Outputable (HsFieldLabel p) # 
Instance details

Defined in Language.Haskell.Syntax.Expr

Methods

ppr :: HsFieldLabel p -> SDoc Source #

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

Defined in GHC.Hs.Expr

Outputable (HsPragE (GhcPass p)) # 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

Defined in GHC.Hs.Expr

Methods

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

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

Outputable (HsLit (GhcPass p)) # 
Instance details

Defined in GHC.Hs.Lit

Methods

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

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

Defined in GHC.Hs.Lit

Methods

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

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

Defined in GHC.Hs.Pat

Methods

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

Outputable (AmbiguousFieldOcc (GhcPass p)) # 
Instance details

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Type

Methods

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

Outputable (FieldOcc pass) # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: FieldOcc pass -> SDoc Source #

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

Defined in GHC.Hs.Type

Methods

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

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Type

Methods

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

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

Defined in GHC.Hs.Type

Methods

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

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

Defined in GHC.Hs.Type

Methods

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

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

Defined in GHC.Hs.Type

Methods

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

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

Defined in GHC.Utils.Outputable

Methods

ppr :: Maybe a -> SDoc Source #

Outputable a => Outputable [a] # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: [a] -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: Either a b -> SDoc Source #

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

Defined in GHC.Utils.Outputable

Methods

ppr :: Map key elt -> SDoc Source #

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

Defined in GHC.CmmToAsm.Reg.Graph.Stats

Methods

ppr :: RegAllocStats statics instr -> SDoc Source #

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

Defined in GHC.Data.Graph.Directed

Methods

ppr :: Node a b -> SDoc Source #

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

Defined in GHC.Data.TrieMap

Methods

ppr :: GenMap m a -> SDoc Source #

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

Defined in GHC.Data.TrieMap

Methods

ppr :: ListMap m a -> SDoc Source #

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

Just print the original expression (the a).

Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsExpansion a b -> SDoc Source #

Outputable (GenLocated Anchor EpaComment) # 
Instance details

Defined in GHC.Parser.Annotation

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

Defined in GHC.Parser.Annotation

Methods

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

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

Defined in GHC.Types.SrcLoc

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

Defined in GHC.Types.Unique.DFM

Methods

ppr :: UniqDFM key a -> SDoc Source #

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

Defined in GHC.Types.Unique.FM

Methods

ppr :: UniqFM key a -> SDoc Source #

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

Defined in GHC.Types.Unique.Map

Methods

ppr :: UniqMap k a -> SDoc Source #

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

Defined in GHC.Types.Unique.SDFM

Methods

ppr :: UniqSDFM key ele -> SDoc Source #

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

Defined in GHC.Core.TyCon

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

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv ArgFlag -> SDoc Source #

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

Defined in GHC.Types.Var

(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) # 
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)) # 
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)) # 
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)) # 
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) # 
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)) # 
Instance details

Defined in GHC.Hs.Expr

Methods

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

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

Defined in Language.Haskell.Syntax.Pat

Methods

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

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

Defined in Language.Haskell.Syntax.Pat

Methods

ppr :: HsRecFields p arg -> SDoc Source #

(Outputable tm, Outputable ty) => Outputable (HsArg tm ty) # 
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)) # 
Instance details

Defined in GHC.Hs.Type

Methods

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

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

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsScaled pass a -> SDoc Source #

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

Defined in GHC.Hs.Type

Methods

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

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

Defined in GHC.Hs.Type

Methods

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

(Outputable a, Outputable b) => Outputable (a, b) # 
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) # 
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) # 
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) # 
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) # 
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) # 
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) # 
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) # 
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 # 
Instance details

Defined in GHC.Core.ConLike

OutputableBndr DataCon # 
Instance details

Defined in GHC.Core.DataCon

OutputableBndr PatSyn # 
Instance details

Defined in GHC.Core.PatSyn

OutputableBndr BinderInfo # 
Instance details

Defined in GHC.Stg.Lift.Analysis

OutputableBndr Name # 
Instance details

Defined in GHC.Types.Name

OutputableBndr OccName # 
Instance details

Defined in GHC.Types.Name.Occurrence

OutputableBndr RdrName # 
Instance details

Defined in GHC.Types.Name.Reader

OutputableBndr Var # 
Instance details

Defined in GHC.Core.Ppr

OutputableBndr HsIPName # 
Instance details

Defined in Language.Haskell.Syntax.Type

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

Defined in GHC.Core.Ppr

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

Defined in GHC.Hs.ImpExp

OutputableBndr (FieldLabelStrings p) # 
Instance details

Defined in Language.Haskell.Syntax.Expr

OutputableBndr (AmbiguousFieldOcc (GhcPass p)) # 
Instance details

Defined in GHC.Hs.Type

OutputableBndr (FieldOcc pass) # 
Instance details

Defined in Language.Haskell.Syntax.Type

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) # 
Instance details

Defined in Language.Haskell.Syntax.Type

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 CmmGraph # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

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

OutputableP Platform CmmInfoTable # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

OutputableP Platform CmmStatic # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

OutputableP Platform CmmTopInfo # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform CLabel # 
Instance details

Defined in GHC.Cmm.CLabel

Methods

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

OutputableP Platform CmmExpr # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

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

OutputableP Platform CmmLit # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

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

OutputableP Platform ForeignTarget # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform LiveInfo # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

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

OutputableP Platform Instr # 
Instance details

Defined in GHC.CmmToAsm.SPARC.Ppr

Methods

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

OutputableP Platform CgLoc # 
Instance details

Defined in GHC.StgToCmm.Closure

Methods

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

OutputableP Platform CgIdInfo # 
Instance details

Defined in GHC.StgToCmm.Monad

Methods

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

OutputableP env Label # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

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

OutputableP env CLabel => OutputableP env DebugBlock # 
Instance details

Defined in GHC.Cmm.DebugBlock

Methods

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

OutputableP env CLabel => OutputableP env UnwindExpr # 
Instance details

Defined in GHC.Cmm.DebugBlock

Methods

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

OutputableP env CLabel => OutputableP env UnwindPoint # 
Instance details

Defined in GHC.Cmm.DebugBlock

Methods

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

OutputableP env GlobalReg # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

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

OutputableP env CLabel => OutputableP env ModuleSRTInfo # 
Instance details

Defined in GHC.Cmm.Info.Build

Methods

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

OutputableP env CLabel => OutputableP env DwarfFrameBlock # 
Instance details

Defined in GHC.CmmToAsm.Dwarf.Types

Methods

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

OutputableP env Alignment # 
Instance details

Defined in GHC.Types.Basic

Methods

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

OutputableP env SDoc # 
Instance details

Defined in GHC.Utils.Outputable

Methods

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

OutputableP Platform (GenCmmStatics a) # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

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

Defined in GHC.Utils.Outputable

Methods

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

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

Defined in GHC.Utils.Outputable

Methods

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

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

Defined in GHC.Cmm

Methods

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

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

Defined in GHC.Cmm

Methods

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

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

Defined in GHC.Cmm.Dataflow.Label

Methods

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

OutputableP env instr => OutputableP env (LiveInstr instr) # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

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

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

Defined in GHC.Utils.Outputable

Methods

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

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

Defined in GHC.Utils.Outputable

Methods

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

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

Defined in GHC.Utils.Outputable

Methods

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

OutputableP Platform (CmmNode e x) # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> CmmNode e x -> SDoc Source #

(OutputableP env key, OutputableP env elt) => OutputableP env (Map key elt) # 
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) # 
Instance details

Defined in GHC.Utils.Outputable

Methods

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

(OutputableP Platform d, OutputableP Platform info, OutputableP Platform i) => OutputableP Platform (GenCmmDecl d info i) # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

Methods

pdoc :: Platform -> GenCmmDecl d info i -> SDoc Source #

OutputableP Platform (Block CmmNode C C) # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Block CmmNode C O) # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Block CmmNode O C) # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Block CmmNode O O) # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Graph CmmNode e x) # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> Graph CmmNode e x -> SDoc Source #

(OutputableP env a, OutputableP env b, OutputableP env c) => OutputableP env (a, b, c) # 
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 # 
Instance details

Defined in GHC.Utils.Outputable

Outputable SDoc # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc Source #

OutputableP env SDoc # 
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) # 
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'

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.

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 #

Constructors

PprUser PrintUnqualified Depth Coloured 
PprDump PrintUnqualified 
PprCode LabelStyle

Print code; either C or assembler

Instances

Instances details
Outputable PprStyle # 
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 # 
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