ghc-8.0.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

Outputable

Contents

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 #

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

Instances

Outputable Bool # 
Outputable Char # 
Outputable Int # 

Methods

ppr :: Int -> SDoc Source #

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

Outputable Int32 # 
Outputable Int64 # 
Outputable Ordering # 
Outputable Word # 
Outputable Word16 # 
Outputable Word32 # 
Outputable () # 

Methods

ppr :: () -> SDoc Source #

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

Outputable Fingerprint # 
Outputable Serialized # 
Outputable PrimOp # 
Outputable OccName # 
Outputable UnitId # 
Outputable ModuleName # 
Outputable Module # 
Outputable Name # 
Outputable FastString # 
Outputable PprStyle # 
Outputable IdDetails # 
Outputable SrcSpan # 
Outputable RealSrcSpan # 
Outputable SrcLoc # 
Outputable RealSrcLoc # 
Outputable HsDocString # 
Outputable MetaDetails # 
Outputable TCvSubst # 
Outputable UnivCoProvenance # 
Outputable LeftOrRight # 
Outputable Coercion # 
Outputable TyThing # 
Outputable TyBinder # 
Outputable Type # 
Outputable IntWithInf # 
Outputable FractionalLit # 
Outputable InlineSpec # 
Outputable InlinePragma # 
Outputable RuleMatchInfo # 
Outputable Activation # 
Outputable CompilerPhase # 
Outputable SuccessFlag # 
Outputable OccInfo # 
Outputable OverlapMode # 
Outputable OverlapFlag # 
Outputable Origin # 
Outputable RecFlag # 
Outputable Boxity # 
Outputable TopLevelFlag # 
Outputable FixityDirection # 
Outputable Fixity # 
Outputable WarningTxt # 
Outputable FunctionOrData # 
Outputable SwapFlag # 
Outputable OneShotInfo # 
Outputable Unique # 
Outputable RegClass # 
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.

Methods

ppr :: Reg -> SDoc Source #

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

Outputable RealReg # 
Outputable VirtualReg # 
Outputable Phase # 
Outputable ModLocation # 
Outputable CType # 
Outputable Header # 
Outputable CCallConv # 
Outputable CCallSpec # 
Outputable CExportSpec # 
Outputable Safety # 
Outputable ForeignCall # 
Outputable PackageName # 
Outputable SourcePackageId # 
Outputable ComponentId # 
Outputable GhcMode # 
Outputable SafeHaskellMode # 
Outputable Width # 
Outputable CmmType # 
Outputable ArgDescr # 
Outputable ClosureTypeInfo # 
Outputable SMRep # 
Outputable StgHalfWord # 
Outputable StgWord # 
Outputable TyCon # 
Outputable Var # 

Methods

ppr :: Var -> SDoc Source #

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

Outputable CoAxiomRule # 
Outputable Role # 
Outputable CoAxBranch # 
Outputable LiftingContext # 
Outputable CostCentreStack # 
Outputable CostCentre # 
Outputable EqSpec # 
Outputable DataCon # 
Outputable PatSyn # 
Outputable ConLike # 
Outputable InScopeSet # 
Outputable ModuleOrigin # 
Outputable AvailInfo # 
Outputable ImportSpec # 
Outputable Parent # 
Outputable GlobalRdrElt # 
Outputable LocalRdrEnv # 
Outputable RdrName # 
Outputable Class # 
Outputable PrimElemRep # 
Outputable PrimRep # 
Outputable AlgTyConFlav # 
Outputable CoercionHole # 
Outputable VisibilityFlag # 
Outputable RepType # 
Outputable EqRel # 
Outputable Literal # 
Outputable StrictnessMark # 
Outputable SrcUnpackedness # 
Outputable SrcStrictness # 
Outputable HsImplBang # 
Outputable HsSrcBang # 
Outputable AltCon # 
Outputable StrictSig # 
Outputable DmdType # 
Outputable CPRResult # 
Outputable TypeShape # 
Outputable Count # 
Outputable UseDmd # 
Outputable StrDmd # 
Outputable TickBoxOp # 
Outputable CafInfo # 
Outputable RecSelParent # 
Outputable CoreStats # 
Outputable UnVarGraph # 
Outputable UnVarSet # 
Outputable FamInstMatch # 
Outputable FamInst # 
Outputable PrimCall # 
Outputable CgBreakInfo # 
Outputable UnlinkedBCO # 
Outputable CompiledByteCode # 
Outputable ForeignLabelSource # 
Outputable CLabel # 
Outputable CmmTickScope # 
Outputable UnwindExpr # 
Outputable DebugBlock # 
Outputable LlvmCastOp # 
Outputable LlvmCmpOp # 
Outputable LlvmMachOp # 
Outputable LlvmLinkageType # 
Outputable LlvmCallConvention # 
Outputable LlvmFuncAttr # 
Outputable LlvmParamAttr # 
Outputable LlvmFunctionDecl # 
Outputable LlvmStatic # 
Outputable LlvmLit # 
Outputable LlvmVar # 
Outputable LlvmType # 
Outputable MetaExpr # 
Outputable TopSRT # 
Outputable ParamLocation # 
Outputable Status # 
Outputable LiveInfo # 
Outputable SpillStats # 
Outputable Loc # 

Methods

ppr :: Loc -> SDoc Source #

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

Outputable UpdateFlag # 
Outputable AltType # 
Outputable TcDepVars # 
Outputable TcLevel # 
Outputable ExpType # 
Outputable IfaceCoercion # 
Outputable IfaceTyCon # 
Outputable IfaceTcArgs # 
Outputable IfaceTyLit # 
Outputable IfaceType # 
Outputable IfaceBndr # 
Outputable ClsInst # 
Outputable Subst # 
Outputable CallCtxt # 
Outputable ArgSummary # 
Outputable CgLoc # 
Outputable ArgRep # 
Outputable Sequel # 
Outputable CgIdInfo # 
Outputable BCInstr # 
Outputable EvCallStack # 
Outputable EvLit # 
Outputable EvTypeable # 
Outputable EvTerm # 
Outputable EvBind # 
Outputable EvBindsVar # 
Outputable TcEvBinds # 
Outputable HsWrapper # 
Outputable OverLitVal # 
Outputable HsLit # 
Outputable HsTyLit # 
Outputable HsIPName # 
Outputable TcSpecPrag # 
Outputable DocDecl # 
Outputable ForeignExport # 
Outputable ForeignImport # 
Outputable NewOrData # 
Outputable PendingTcSplice # 
Outputable PendingRnSplice # 
Outputable UnboundVar # 
Outputable PmLit # 
Outputable PmExpr # 
Outputable AnnotationComment # 
Outputable AnnKeywordId # 
Outputable Token # 
Outputable Annotation # 
Outputable IfaceConAlt # 
Outputable IfaceExpr # 
Outputable IfaceIdDetails # 
Outputable IfaceUnfolding # 
Outputable IfaceInfoItem # 
Outputable IfaceIdInfo # 
Outputable IfaceAnnotation # 
Outputable IfaceRule # 
Outputable IfaceFamInst # 
Outputable IfaceClsInst # 
Outputable IfaceAT # 
Outputable IfaceClassOp # 
Outputable IfaceTyConParent # 
Outputable IfaceDecl # 
Outputable Unlinked # 
Outputable Linkable # 
Outputable IfaceTrustInfo # 
Outputable IfaceVectInfo # 
Outputable VectInfo # 
Outputable ModSummary # 
Outputable FixItem # 
Outputable InteractiveImport # 
Outputable TargetId # 
Outputable Target # 
Outputable FloatBind # 
Outputable PhasePlus # 
Outputable TypeOrKind # 
Outputable ErrorThing # 
Outputable CtOrigin # 
Outputable SkolemInfo # 
Outputable SubGoalDepth # 
Outputable CtFlavour # 
Outputable CtEvidence # 
Outputable TcEvDest # 
Outputable ImplicStatus # 
Outputable Implication # 
Outputable WantedConstraints # 
Outputable Ct # 

Methods

ppr :: Ct -> SDoc Source #

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

Outputable TcPatSynInfo # 
Outputable TcIdSigBndr # 
Outputable TcIdSigInfo # 
Outputable TcSigInfo # 
Outputable WhereFrom # 
Outputable PromotionErr # 
Outputable TcTyThing # 
Outputable ThStage # 
Outputable TcIdBinder # 
Outputable Tick # 
Outputable FloatOutSwitches # 
Outputable SimplifierMode # 
Outputable CoreToDo # 
Outputable FloatSpec # 
Outputable Level # 
Outputable Floats # 
Outputable SimplSR # 
Outputable ArgSpec # 
Outputable DupFlag # 
Outputable SimplCont # 
Outputable EquationInfo # 
Outputable InertCans # 
Outputable InertSet # 
Outputable WorkList # 
Outputable ClosureType # 
Outputable Term # 
Outputable CompRepr # 
Outputable ProdRepr # 
Outputable ConRepr # 
Outputable SumRepr # 
Outputable CoreModule # 
Outputable a => Outputable [a] # 

Methods

ppr :: [a] -> SDoc Source #

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

Outputable a => Outputable (Maybe a) # 

Methods

ppr :: Maybe a -> SDoc Source #

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

Outputable a => Outputable (SCC a) # 

Methods

ppr :: SCC a -> SDoc Source #

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

Outputable elt => Outputable (IntMap elt) # 

Methods

ppr :: IntMap elt -> SDoc Source #

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

Outputable a => Outputable (Set a) # 

Methods

ppr :: Set a -> SDoc Source #

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

Outputable node => Outputable (Graph node) # 

Methods

ppr :: Graph node -> SDoc Source #

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

Outputable a => Outputable (OrdList a) # 
Outputable a => Outputable (Pair a) # 

Methods

ppr :: Pair a -> SDoc Source #

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

Outputable a => Outputable (Bag a) # 

Methods

ppr :: Bag a -> SDoc Source #

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

Outputable (DefMethSpec ty) # 
Outputable a => Outputable (UniqFM a) # 

Methods

ppr :: UniqFM a -> SDoc Source #

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

Outputable a => Outputable (BooleanFormula a) # 
Outputable a => Outputable (UniqDFM a) # 
Outputable a => Outputable (OccEnv a) # 

Methods

ppr :: OccEnv a -> SDoc Source #

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

Outputable a => Outputable (FieldLbl a) # 
(HasOccName name, OutputableBndr name) => Outputable (IE name) # 

Methods

ppr :: IE name -> SDoc Source #

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

(OutputableBndr name, HasOccName name) => Outputable (ImportDecl name) # 

Methods

ppr :: ImportDecl name -> SDoc Source #

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

Outputable (CoAxiom br) # 

Methods

ppr :: CoAxiom br -> SDoc Source #

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

Outputable a => Outputable (UnifyResultM a) # 
Outputable b => Outputable (TaggedBndr b) # 
Outputable a => Outputable (CoreMap a) # 
Outputable instr => Outputable (ListGraph instr) # 

Methods

ppr :: ListGraph instr -> SDoc Source #

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

Outputable instr => Outputable (GenBasicBlock instr) # 
Outputable instr => Outputable (LiveInstr instr) # 

Methods

ppr :: LiveInstr instr -> SDoc Source #

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

Outputable instr => Outputable (InstrSR instr) # 

Methods

ppr :: InstrSR instr -> SDoc Source #

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

Outputable bdee => Outputable (GenStgArg bdee) # 

Methods

ppr :: GenStgArg bdee -> SDoc Source #

pprPrec :: Rational -> GenStgArg bdee -> SDoc Source #

Outputable a => Outputable (NonVoid a) # 
Outputable a => Outputable (ProtoBCO a) # 
OutputableBndr name => Outputable (Pat name) # 

Methods

ppr :: Pat name -> SDoc Source #

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

OutputableBndr id => Outputable (SyntaxExpr id) # 
OutputableBndr id => Outputable (HsSplice id) # 
OutputableBndr id => Outputable (HsCmd id) # 

Methods

ppr :: HsCmd id -> SDoc Source #

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

OutputableBndr id => Outputable (HsExpr id) # 

Methods

ppr :: HsExpr id -> SDoc Source #

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

OutputableBndr id => Outputable (HsOverLit id) # 
Outputable (AmbiguousFieldOcc name) # 
Outputable (FieldOcc name) # 

Methods

ppr :: FieldOcc name -> SDoc Source #

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

OutputableBndr name => Outputable (ConDeclField name) # 
OutputableBndr name => Outputable (HsAppType name) # 

Methods

ppr :: HsAppType name -> SDoc Source #

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

Outputable (HsWildCardInfo name) # 
OutputableBndr name => Outputable (HsType name) # 

Methods

ppr :: HsType name -> SDoc Source #

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

OutputableBndr name => Outputable (HsTyVarBndr name) # 
OutputableBndr name => Outputable (LHsQTyVars name) # 

Methods

ppr :: LHsQTyVars name -> SDoc Source #

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

Outputable a => Outputable (RecordPatSynField a) # 
OutputableBndr name => Outputable (FixitySig name) # 

Methods

ppr :: FixitySig name -> SDoc Source #

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

OutputableBndr name => Outputable (Sig name) # 

Methods

ppr :: Sig name -> SDoc Source #

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

OutputableBndr id => Outputable (IPBind id) # 

Methods

ppr :: IPBind id -> SDoc Source #

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

OutputableBndr id => Outputable (HsIPBinds id) # 
OutputableBndr id => Outputable (ABExport id) # 
OutputableBndr name => Outputable (RoleAnnotDecl name) # 
OutputableBndr name => Outputable (AnnDecl name) # 

Methods

ppr :: AnnDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (WarnDecl name) # 

Methods

ppr :: WarnDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (WarnDecls name) # 

Methods

ppr :: WarnDecls name -> SDoc Source #

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

OutputableBndr name => Outputable (VectDecl name) # 

Methods

ppr :: VectDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (RuleBndr name) # 

Methods

ppr :: RuleBndr name -> SDoc Source #

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

OutputableBndr name => Outputable (RuleDecl name) # 

Methods

ppr :: RuleDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (RuleDecls name) # 

Methods

ppr :: RuleDecls name -> SDoc Source #

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

OutputableBndr name => Outputable (ForeignDecl name) # 
OutputableBndr name => Outputable (DefaultDecl name) # 
OutputableBndr name => Outputable (DerivDecl name) # 

Methods

ppr :: DerivDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (InstDecl name) # 

Methods

ppr :: InstDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (ClsInstDecl name) # 
OutputableBndr name => Outputable (DataFamInstDecl name) # 
OutputableBndr name => Outputable (TyFamInstDecl name) # 
OutputableBndr name => Outputable (ConDecl name) # 

Methods

ppr :: ConDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (HsDataDefn name) # 

Methods

ppr :: HsDataDefn name -> SDoc Source #

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

Outputable (FamilyInfo name) # 

Methods

ppr :: FamilyInfo name -> SDoc Source #

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

OutputableBndr name => Outputable (FamilyDecl name) # 

Methods

ppr :: FamilyDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (TyClGroup name) # 

Methods

ppr :: TyClGroup name -> SDoc Source #

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

OutputableBndr name => Outputable (TyClDecl name) # 

Methods

ppr :: TyClDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (SpliceDecl name) # 

Methods

ppr :: SpliceDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (HsGroup name) # 

Methods

ppr :: HsGroup name -> SDoc Source #

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

OutputableBndr name => Outputable (HsDecl name) # 

Methods

ppr :: HsDecl name -> SDoc Source #

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

OutputableBndr id => Outputable (ArithSeqInfo id) # 
OutputableBndr id => Outputable (HsBracket id) # 
OutputableBndr id => Outputable (HsSplicedThing id) # 
OutputableBndr id => Outputable (HsCmdTop id) # 
(OutputableBndr name, HasOccName name) => Outputable (HsModule name) # 

Methods

ppr :: HsModule name -> SDoc Source #

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

Outputable name => Outputable (AnnTarget name) # 

Methods

ppr :: AnnTarget name -> SDoc Source #

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

OutputableBndr a => Outputable (InstInfo a) # 
Outputable a => Outputable (StopOrContinue a) # 
(Outputable a, Outputable b) => Outputable (Either a b) # 

Methods

ppr :: Either a b -> SDoc Source #

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

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

Methods

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

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

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

Methods

ppr :: Map key elt -> SDoc Source #

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

(Outputable l, Outputable e) => Outputable (GenLocated l e) # 
(Outputable statics, Outputable instr) => Outputable (RegAllocStats statics instr) # 

Methods

ppr :: RegAllocStats statics instr -> SDoc Source #

pprPrec :: Rational -> RegAllocStats statics instr -> SDoc Source #

(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgRhs bndr bdee) # 

Methods

ppr :: GenStgRhs bndr bdee -> SDoc Source #

pprPrec :: Rational -> GenStgRhs bndr bdee -> SDoc Source #

(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgExpr bndr bdee) # 

Methods

ppr :: GenStgExpr bndr bdee -> SDoc Source #

pprPrec :: Rational -> GenStgExpr bndr bdee -> SDoc Source #

(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgBinding bndr bdee) # 

Methods

ppr :: GenStgBinding bndr bdee -> SDoc Source #

pprPrec :: Rational -> GenStgBinding bndr bdee -> SDoc Source #

(Outputable arg, Outputable rec) => Outputable (HsConDetails arg rec) # 

Methods

ppr :: HsConDetails arg rec -> SDoc Source #

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

Outputable thing => Outputable (HsWildCardBndrs name thing) # 

Methods

ppr :: HsWildCardBndrs name thing -> SDoc Source #

pprPrec :: Rational -> HsWildCardBndrs name thing -> SDoc Source #

Outputable thing => Outputable (HsImplicitBndrs name thing) # 

Methods

ppr :: HsImplicitBndrs name thing -> SDoc Source #

pprPrec :: Rational -> HsImplicitBndrs name thing -> SDoc Source #

(OutputableBndr idL, OutputableBndr idR) => Outputable (PatSynBind idL idR) # 

Methods

ppr :: PatSynBind idL idR -> SDoc Source #

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

(OutputableBndr idL, OutputableBndr idR) => Outputable (HsBindLR idL idR) # 

Methods

ppr :: HsBindLR idL idR -> SDoc Source #

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

(OutputableBndr idL, OutputableBndr idR) => Outputable (HsValBindsLR idL idR) # 

Methods

ppr :: HsValBindsLR idL idR -> SDoc Source #

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

(OutputableBndr idL, OutputableBndr idR) => Outputable (HsLocalBindsLR idL idR) # 

Methods

ppr :: HsLocalBindsLR idL idR -> SDoc Source #

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

(Outputable id, Outputable arg) => Outputable (HsRecField' id arg) # 

Methods

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

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

Outputable arg => Outputable (HsRecFields id arg) # 

Methods

ppr :: HsRecFields id arg -> SDoc Source #

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

OutputableBndr idL => Outputable (ParStmtBlock idL idR) # 

Methods

ppr :: ParStmtBlock idL idR -> SDoc Source #

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

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

Methods

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

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

(OutputableBndr idL, OutputableBndr idR, Outputable body) => Outputable (StmtLR idL idR body) # 

Methods

ppr :: StmtLR idL idR body -> SDoc Source #

pprPrec :: Rational -> StmtLR idL idR body -> SDoc Source #

(Outputable a, Outputable b, Outputable c, Outputable d) => Outputable (a, b, c, d) # 

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

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

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

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

OutputableBndr OccName # 
OutputableBndr Name # 
OutputableBndr DataCon # 
OutputableBndr PatSyn # 
OutputableBndr ConLike # 
OutputableBndr RdrName # 
OutputableBndr HsIPName # 
Outputable b => OutputableBndr (TaggedBndr b) # 
OutputableBndr (AmbiguousFieldOcc name) # 

Pretty printing combinators

data SDoc Source #

Instances

runSDoc :: SDoc -> SDocContext -> Doc 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.

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.

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"

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

Apply the given colour/style for the argument.

Only takes effect if colours are enabled.

data PprColour Source #

A colour/style for use with coloured.

Converting SDoc into strings and outputing it

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.

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.

Constructors

LambdaBind 
CaseBind 
LetBind 

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 an original name, this function tells you which module name it should be qualified with when printing for the user, if any. For example, given Control.Exception.catch, which is in scope as Exception.catch, this function will return Just Exception. Note that the return value is a ModuleName, not a Module, because in source code, names are qualified by ModuleNames.

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 = UnitId -> Bool Source #

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

alwaysQualifyNames :: QueryQualifyName Source #

NB: This won't ever show package IDs

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

Truncate a list that is longer than the current depth.

mkErrStyle :: DynFlags -> PrintUnqualified -> PprStyle Source #

Style for printing error messages

data Depth Source #

Constructors

AllTheWay 
PartWay Int 

Error handling and debugging utilities

pprPanic :: 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 :: (?callStack :: CallStack) => String -> Int -> SDoc -> a Source #

Panic with an assertation 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

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

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

warnPprTrace :: 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 :: (?callStack :: CallStack) => SDoc -> a -> a Source #

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

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.

trace ("calling f with x = " ++ show x) (f x)

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 an failed assertion exception for a given filename and line number.

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