ghc-8.2.1: 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 Source # 
Outputable Char Source # 
Outputable Int Source # 

Methods

ppr :: Int -> SDoc Source #

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

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

Methods

ppr :: () -> SDoc Source #

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

Outputable Fingerprint Source # 
Outputable Extension Source # 
Outputable Serialized Source # 
Outputable Name Source # 
Outputable OccName Source # 
Outputable PrimOp Source # 
Outputable TyCon Source # 
Outputable FastString Source # 
Outputable ComponentId Source # 
Outputable InstalledUnitId Source # 
Outputable UnitId Source # 
Outputable ModuleName Source # 
Outputable Module Source # 
Outputable QualifyName Source # 
Outputable PprStyle Source # 
Outputable TyBinder Source # 
Outputable TCvSubst Source # 
Outputable UnivCoProvenance Source # 
Outputable Coercion Source # 
Outputable TyThing Source # 
Outputable Type Source # 
Outputable MetaDetails Source # 
Outputable SrcSpan Source # 
Outputable RealSrcSpan Source # 
Outputable SrcLoc Source # 
Outputable RealSrcLoc Source # 
Outputable IdDetails Source # 
Outputable HsDocString Source # 
Outputable IntWithInf Source # 
Outputable FractionalLit Source # 
Outputable InlineSpec Source # 
Outputable InlinePragma Source # 
Outputable RuleMatchInfo Source # 
Outputable Activation Source # 
Outputable CompilerPhase Source # 
Outputable SourceText Source # 
Outputable SuccessFlag Source # 
Outputable TailCallInfo Source # 
Outputable OccInfo Source # 
Outputable OverlapMode Source # 
Outputable OverlapFlag Source # 
Outputable DerivStrategy Source # 
Outputable Origin Source # 
Outputable RecFlag Source # 
Outputable Boxity Source # 
Outputable TopLevelFlag Source # 
Outputable LexicalFixity Source # 
Outputable FixityDirection Source # 
Outputable Fixity Source # 
Outputable WarningTxt Source # 
Outputable StringLiteral Source # 
Outputable FunctionOrData Source # 
Outputable SwapFlag Source # 
Outputable OneShotInfo Source # 
Outputable LeftOrRight Source # 
Outputable Unique Source # 
Outputable RegClass Source # 
Outputable Reg Source #

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

Methods

ppr :: Reg -> SDoc Source #

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

Outputable RealReg Source # 
Outputable VirtualReg Source # 
Outputable DefUnitId Source # 
Outputable InstalledModule Source # 
Outputable IndefModule Source # 
Outputable IndefUnitId Source # 
Outputable ModLocation Source # 
Outputable PackageName Source # 
Outputable SourcePackageId Source # 
Outputable CType Source # 
Outputable Header Source # 
Outputable CCallConv Source # 
Outputable CCallSpec Source # 
Outputable CExportSpec Source # 
Outputable Safety Source # 
Outputable ForeignCall Source # 
Outputable Phase Source # 
Outputable PackageFlag Source # 
Outputable ModRenaming Source # 
Outputable PackageArg Source # 
Outputable GhcMode Source # 
Outputable SafeHaskellMode Source # 
Outputable Language Source # 
Outputable WarnReason Source # 
Outputable ArgDescr Source # 
Outputable ClosureTypeInfo Source # 
Outputable SMRep Source # 
Outputable StgHalfWord Source # 
Outputable StgWord Source # 
Outputable Annotation Source # 
Outputable ModuleOrigin Source # 
Outputable Width Source # 
Outputable CmmType Source # 
Outputable AvailInfo Source # 
Outputable ImportSpec Source # 
Outputable Parent Source # 
Outputable GlobalRdrElt Source # 
Outputable LocalRdrEnv Source # 
Outputable RdrName Source # 
Outputable AnnotationComment Source # 
Outputable AnnKeywordId Source # 
Outputable Token Source # 
Outputable ArgFlag Source # 
Outputable Var Source # 

Methods

ppr :: Var -> SDoc Source #

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

Outputable PatSyn Source # 
Outputable EqSpec Source # 
Outputable DataCon Source # 
Outputable ConLike Source # 
Outputable CostCentreStack Source # 
Outputable CostCentre Source # 
Outputable CoAxiomRule Source # 
Outputable Role Source # 
Outputable CoAxBranch Source # 
Outputable LiftingContext Source # 
Outputable Class Source # 
Outputable PrimElemRep Source # 
Outputable PrimRep Source # 
Outputable FamTyConFlav Source # 
Outputable AlgTyConFlav Source # 
Outputable IfaceTcArgs Source # 
Outputable IfaceCoercion Source # 
Outputable IfaceTyLit Source # 
Outputable IfaceTyCon Source # 
Outputable IfaceType Source # 
Outputable IfaceBndr Source # 
Outputable InScopeSet Source # 
Outputable CoercionHole Source # 
Outputable EqRel Source # 
Outputable Literal Source # 
Outputable StrictnessMark Source # 
Outputable SrcUnpackedness Source # 
Outputable SrcStrictness Source # 
Outputable HsImplBang Source # 
Outputable HsSrcBang Source # 
Outputable SlotTy Source # 
Outputable StrictSig Source # 
Outputable DmdType Source # 
Outputable CPRResult Source # 
Outputable TypeShape Source # 
Outputable Count Source # 
Outputable UseDmd Source # 
Outputable StrDmd Source # 
Outputable AltCon Source # 
Outputable FamInstMatch Source # 
Outputable FamInst Source # 
Outputable LevityInfo Source # 
Outputable TickBoxOp Source # 
Outputable CafInfo Source # 
Outputable RecSelParent Source # 
Outputable UnVarGraph Source # 
Outputable UnVarSet Source # 
Outputable PrimCall Source # 
Outputable CgBreakInfo Source # 
Outputable UnlinkedBCO Source # 
Outputable CompiledByteCode Source # 
Outputable CoreStats Source # 
Outputable UpdateFlag Source # 
Outputable AltType Source # 
Outputable ShowHowMuch Source # 
Outputable IfaceJoinInfo Source # 
Outputable IfaceConAlt Source # 
Outputable IfaceExpr Source # 
Outputable IfaceIdDetails Source # 
Outputable IfaceUnfolding Source # 
Outputable IfaceInfoItem Source # 
Outputable IfaceIdInfo Source # 
Outputable IfaceCompleteMatch Source # 
Outputable IfaceAnnotation Source # 
Outputable IfaceRule Source # 
Outputable IfaceFamInst Source # 
Outputable IfaceClsInst Source # 
Outputable IfaceAT Source # 
Outputable IfaceClassOp Source # 
Outputable IfaceTyConParent Source # 
Outputable IfaceDecl Source # 
Outputable ForeignLabelSource Source # 
Outputable CLabel Source # 
Outputable CmmTickScope Source # 
Outputable LlvmCastOp Source # 
Outputable LlvmCmpOp Source # 
Outputable LlvmMachOp Source # 
Outputable LlvmLinkageType Source # 
Outputable LlvmCallConvention Source # 
Outputable LlvmFuncAttr Source # 
Outputable LlvmParamAttr Source # 
Outputable LlvmFunctionDecl Source # 
Outputable LlvmStatic Source # 
Outputable LlvmLit Source # 
Outputable LlvmVar Source # 
Outputable LlvmType Source # 
Outputable MetaExpr Source # 
Outputable MetaId Source # 
Outputable LiveInfo Source # 
Outputable Loc Source # 

Methods

ppr :: Loc -> SDoc Source #

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

Outputable SpillStats Source # 
Outputable UnwindExpr Source # 
Outputable UnwindPoint Source # 
Outputable DebugBlock Source # 
Outputable Status Source # 
Outputable ParamLocation Source # 
Outputable TopSRT Source # 
Outputable CandidatesQTvs Source # 
Outputable TcLevel Source # 
Outputable InferResult Source # 
Outputable ExpType Source # 
Outputable EvCallStack Source # 
Outputable EvLit Source # 
Outputable EvTypeable Source # 
Outputable EvTerm Source # 
Outputable EvBind Source # 
Outputable EvBindMap Source # 
Outputable EvBindsVar Source # 
Outputable TcEvBinds Source # 
Outputable HsWrapper Source # 
Outputable HsTyLit Source # 
Outputable HsIPName Source # 
Outputable OverLitVal Source # 
Outputable HsLit Source # 
Outputable TcSpecPrag Source # 
Outputable CgLoc Source # 
Outputable Sequel Source # 
Outputable CgIdInfo Source # 
Outputable ArgRep Source # 
Outputable ClsInst Source # 
Outputable DocDecl Source # 
Outputable ForeignExport Source # 
Outputable ForeignImport Source # 
Outputable NewOrData Source # 
Outputable PendingTcSplice Source # 
Outputable PendingRnSplice Source # 
Outputable SpliceDecoration Source # 
Outputable UnboundVar Source # 
Outputable PmLit Source # 
Outputable PmExpr Source # 
Outputable CompleteMatch Source # 
Outputable Unlinked Source # 
Outputable Linkable Source # 
Outputable IfaceTrustInfo Source # 
Outputable IfaceVectInfo Source # 
Outputable VectInfo Source # 
Outputable ModSummary Source # 
Outputable FixItem Source # 
Outputable InteractiveImport Source # 
Outputable SptEntry Source # 
Outputable TargetId Source # 
Outputable Target Source # 
Outputable TypeOrKind Source # 
Outputable ErrorThing Source # 
Outputable CtOrigin Source # 
Outputable SkolemInfo Source # 
Outputable SubGoalDepth Source # 
Outputable CtFlavour Source # 
Outputable CtEvidence Source # 
Outputable TcEvDest Source # 
Outputable ImplicStatus Source # 
Outputable Implication Source # 
Outputable WantedConstraints Source # 
Outputable Ct Source # 

Methods

ppr :: Ct -> SDoc Source #

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

Outputable TcPatSynInfo Source # 
Outputable TcIdSigInst Source # 
Outputable TcIdSigInfo Source # 
Outputable TcSigInfo Source # 
Outputable WhereFrom Source # 
Outputable IdBindingInfo Source # 
Outputable PromotionErr Source # 
Outputable TcTyThing Source # 
Outputable ThStage Source # 
Outputable TcIdBinder Source # 
Outputable PhasePlus Source # 
Outputable HsComponentId Source # 
Outputable FloatBind Source # 
Outputable Subst Source # 
Outputable CallCtxt Source # 
Outputable ArgSummary Source # 
Outputable Tick Source # 
Outputable FloatOutSwitches Source # 
Outputable SimplifierMode Source # 
Outputable CoreToDo Source # 
Outputable Floats Source # 
Outputable SimplSR Source # 
Outputable ArgSpec Source # 
Outputable DupFlag Source # 
Outputable SimplCont Source # 
Outputable FloatSpec Source # 
Outputable Level Source # 
Outputable HsSigCtxt Source # 
Outputable ClosureType Source # 
Outputable Term Source # 
Outputable InertCans Source # 
Outputable InertSet Source # 
Outputable WorkList Source # 
Outputable FlattenMode Source # 
Outputable InferMode Source # 
Outputable ThetaOrigin Source # 
Outputable PredOrigin Source # 
Outputable DerivSpecMechanism Source # 
Outputable BCInstr Source # 
Outputable LetBndrSpec Source # 
Outputable EquationInfo Source # 
Outputable DsMatchContext Source # 
Outputable CompRepr Source # 
Outputable ProdRepr Source # 
Outputable ConRepr Source # 
Outputable SumRepr Source # 
Outputable DwarfFrameBlock Source # 
Outputable CoreModule Source # 
Outputable a => Outputable [a] Source # 

Methods

ppr :: [a] -> SDoc Source #

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

Outputable a => Outputable (Maybe a) Source # 

Methods

ppr :: Maybe a -> SDoc Source #

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

Outputable elt => Outputable (IntMap elt) Source # 

Methods

ppr :: IntMap elt -> SDoc Source #

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

Outputable a => Outputable (SCC a) Source # 

Methods

ppr :: SCC a -> SDoc Source #

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

Outputable a => Outputable (Set a) Source # 

Methods

ppr :: Set a -> SDoc Source #

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

Outputable a => Outputable (Pair a) Source # 

Methods

ppr :: Pair a -> SDoc Source #

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

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

Methods

ppr :: UniqFM a -> SDoc Source #

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

Outputable a => Outputable (UniqSet a) Source # 
Outputable a => Outputable (UniqDFM a) Source # 
OutputableBndr a => Outputable (BooleanFormula a) Source # 
Outputable node => Outputable (Graph node) Source # 

Methods

ppr :: Graph node -> SDoc Source #

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

Outputable a => Outputable (Bag a) Source # 

Methods

ppr :: Bag a -> SDoc Source #

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

Outputable a => Outputable (OccEnv a) Source # 

Methods

ppr :: OccEnv a -> SDoc Source #

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

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

Methods

ppr :: IE name -> SDoc Source #

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

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

Methods

ppr :: ImportDecl name -> SDoc Source #

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

Outputable name => Outputable (AnnTarget name) Source # 

Methods

ppr :: AnnTarget name -> SDoc Source #

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

Outputable (CoAxiom br) Source # 

Methods

ppr :: CoAxiom br -> SDoc Source #

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

Outputable a => Outputable (UnifyResultM a) Source # 
Outputable b => Outputable (TaggedBndr b) Source # 
Outputable a => Outputable (CoreMap a) Source # 
Outputable bdee => Outputable (GenStgArg bdee) Source # 

Methods

ppr :: GenStgArg bdee -> SDoc Source #

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

Outputable instr => Outputable (ListGraph instr) Source # 

Methods

ppr :: ListGraph instr -> SDoc Source #

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

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

Methods

ppr :: LiveInstr instr -> SDoc Source #

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

Outputable instr => Outputable (InstrSR instr) Source # 

Methods

ppr :: InstrSR instr -> SDoc Source #

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

OutputableBndrId name => Outputable (Pat name) Source # 

Methods

ppr :: Pat name -> SDoc Source #

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

OutputableBndrId id => Outputable (SyntaxExpr id) Source # 
OutputableBndrId id => Outputable (HsSplice id) Source # 
OutputableBndrId id => Outputable (HsCmd id) Source # 

Methods

ppr :: HsCmd id -> SDoc Source #

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

OutputableBndrId id => Outputable (HsExpr id) Source # 

Methods

ppr :: HsExpr id -> SDoc Source #

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

Outputable (AmbiguousFieldOcc name) Source # 
Outputable (FieldOcc name) Source # 

Methods

ppr :: FieldOcc name -> SDoc Source #

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

OutputableBndrId name => Outputable (ConDeclField name) Source # 
OutputableBndrId name => Outputable (HsAppType name) Source # 

Methods

ppr :: HsAppType name -> SDoc Source #

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

Outputable (HsWildCardInfo name) Source # 
OutputableBndrId name => Outputable (HsType name) Source # 

Methods

ppr :: HsType name -> SDoc Source #

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

OutputableBndrId name => Outputable (HsTyVarBndr name) Source # 
OutputableBndrId name => Outputable (LHsQTyVars name) Source # 

Methods

ppr :: LHsQTyVars name -> SDoc Source #

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

OutputableBndrId id => Outputable (HsOverLit id) Source # 
Outputable a => Outputable (RecordPatSynField a) Source # 
OutputableBndr name => Outputable (FixitySig name) Source # 

Methods

ppr :: FixitySig name -> SDoc Source #

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

OutputableBndrId name => Outputable (Sig name) Source # 

Methods

ppr :: Sig name -> SDoc Source #

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

OutputableBndrId id => Outputable (IPBind id) Source # 

Methods

ppr :: IPBind id -> SDoc Source #

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

OutputableBndrId id => Outputable (HsIPBinds id) Source # 
OutputableBndr id => Outputable (ABExport id) Source # 
Outputable a => Outputable (NonVoid a) Source # 
OutputableBndr name => Outputable (RoleAnnotDecl name) Source # 
OutputableBndrId name => Outputable (AnnDecl name) Source # 

Methods

ppr :: AnnDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (WarnDecl name) Source # 

Methods

ppr :: WarnDecl name -> SDoc Source #

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

OutputableBndr name => Outputable (WarnDecls name) Source # 

Methods

ppr :: WarnDecls name -> SDoc Source #

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

OutputableBndrId name => Outputable (VectDecl name) Source # 

Methods

ppr :: VectDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (RuleBndr name) Source # 

Methods

ppr :: RuleBndr name -> SDoc Source #

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

OutputableBndrId name => Outputable (RuleDecl name) Source # 

Methods

ppr :: RuleDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (RuleDecls name) Source # 

Methods

ppr :: RuleDecls name -> SDoc Source #

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

OutputableBndrId name => Outputable (ForeignDecl name) Source # 
OutputableBndrId name => Outputable (DefaultDecl name) Source # 
OutputableBndrId name => Outputable (DerivDecl name) Source # 

Methods

ppr :: DerivDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (InstDecl name) Source # 

Methods

ppr :: InstDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (ClsInstDecl name) Source # 
OutputableBndrId name => Outputable (DataFamInstDecl name) Source # 
OutputableBndrId name => Outputable (TyFamInstDecl name) Source # 
OutputableBndrId name => Outputable (ConDecl name) Source # 

Methods

ppr :: ConDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (HsDerivingClause name) Source # 
OutputableBndrId name => Outputable (HsDataDefn name) Source # 

Methods

ppr :: HsDataDefn name -> SDoc Source #

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

Outputable (FamilyInfo name) Source # 

Methods

ppr :: FamilyInfo name -> SDoc Source #

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

OutputableBndrId name => Outputable (FamilyDecl name) Source # 

Methods

ppr :: FamilyDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (TyClGroup name) Source # 

Methods

ppr :: TyClGroup name -> SDoc Source #

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

OutputableBndrId name => Outputable (TyClDecl name) Source # 

Methods

ppr :: TyClDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (SpliceDecl name) Source # 

Methods

ppr :: SpliceDecl name -> SDoc Source #

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

OutputableBndrId name => Outputable (HsGroup name) Source # 

Methods

ppr :: HsGroup name -> SDoc Source #

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

OutputableBndrId name => Outputable (HsDecl name) Source # 

Methods

ppr :: HsDecl name -> SDoc Source #

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

(Outputable id, Outputable (NameOrRdrName id)) => Outputable (HsStmtContext id) Source # 
OutputableBndr id => Outputable (HsMatchContext id) Source # 
OutputableBndrId id => Outputable (ArithSeqInfo id) Source # 
OutputableBndrId id => Outputable (HsBracket id) Source # 
OutputableBndrId id => Outputable (HsSplicedThing id) Source # 
OutputableBndrId id => Outputable (HsCmdTop id) Source # 
(OutputableBndrId name, HasOccName name) => Outputable (HsModule name) Source # 

Methods

ppr :: HsModule name -> SDoc Source #

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

OutputableBndrId a => Outputable (InstInfo a) Source # 
Outputable (FunDepEqn a) Source # 
Outputable a => Outputable (StopOrContinue a) Source # 
Outputable theta => Outputable (DerivSpec theta) Source # 

Methods

ppr :: DerivSpec theta -> SDoc Source #

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

Outputable a => Outputable (ProtoBCO a) Source # 
(Outputable a, Outputable b) => Outputable (Either a b) Source # 

Methods

ppr :: Either a b -> SDoc Source #

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

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

Methods

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

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

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

Methods

ppr :: Map key elt -> SDoc Source #

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

(Outputable l, Outputable e) => Outputable (GenLocated l e) Source # 
Outputable tv => Outputable (TyVarBndr tv ArgFlag) Source # 
Outputable tv => Outputable (TyVarBndr tv TyConBndrVis) Source # 
(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgRhs bndr bdee) Source # 

Methods

ppr :: GenStgRhs bndr bdee -> SDoc Source #

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

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

Methods

ppr :: GenStgExpr bndr bdee -> SDoc Source #

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

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

Methods

ppr :: GenStgBinding bndr bdee -> SDoc Source #

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

(OutputableBndr bndr, Outputable bdee, Ord bdee) => Outputable (GenStgTopBinding bndr bdee) Source # 

Methods

ppr :: GenStgTopBinding bndr bdee -> SDoc Source #

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

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

Methods

ppr :: HsConDetails arg rec -> SDoc Source #

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

Outputable thing => Outputable (HsWildCardBndrs name thing) Source # 

Methods

ppr :: HsWildCardBndrs name thing -> SDoc Source #

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

Outputable thing => Outputable (HsImplicitBndrs name thing) Source # 

Methods

ppr :: HsImplicitBndrs name thing -> SDoc Source #

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

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

Methods

ppr :: PatSynBind idL idR -> SDoc Source #

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

(OutputableBndrId idL, OutputableBndrId idR) => Outputable (HsBindLR idL idR) Source # 

Methods

ppr :: HsBindLR idL idR -> SDoc Source #

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

(OutputableBndrId idL, OutputableBndrId idR) => Outputable (HsValBindsLR idL idR) Source # 

Methods

ppr :: HsValBindsLR idL idR -> SDoc Source #

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

(OutputableBndrId idL, OutputableBndrId idR) => Outputable (HsLocalBindsLR idL idR) Source # 

Methods

ppr :: HsLocalBindsLR idL idR -> SDoc Source #

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

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

Methods

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

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

Outputable arg => Outputable (HsRecFields id arg) Source # 

Methods

ppr :: HsRecFields id arg -> SDoc Source #

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

OutputableBndrId idL => Outputable (ParStmtBlock idL idR) Source # 

Methods

ppr :: ParStmtBlock idL idR -> SDoc Source #

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

(OutputableBndrId idR, Outputable body) => Outputable (Match idR body) Source # 

Methods

ppr :: Match idR body -> SDoc Source #

pprPrec :: Rational -> Match idR body -> SDoc Source #

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

Methods

ppr :: RegAllocStats statics instr -> SDoc Source #

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

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

Methods

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

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

(OutputableBndrId idL, OutputableBndrId idR, Outputable body) => Outputable (StmtLR idL idR body) Source # 

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

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 Name Source # 
OutputableBndr OccName Source # 
OutputableBndr RdrName Source # 
OutputableBndr PatSyn Source # 
OutputableBndr DataCon Source # 
OutputableBndr ConLike Source # 
OutputableBndr HsIPName Source # 
(OutputableBndr name, HasOccName name) => OutputableBndr (IEWrappedName name) Source # 
OutputableBndr (AmbiguousFieldOcc name) Source # 

Pretty printing combinators

data SDoc Source #

Represents a pretty-printable document.

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

Instances

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.

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"

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 outputing it

printSDoc :: Mode -> DynFlags -> Handle -> PprStyle -> 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 :: Mode -> DynFlags -> Handle -> PprStyle -> SDoc -> IO () Source #

Like printSDoc but appends an extra newline.

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

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

bufLeftRenderSDoc :: DynFlags -> BufHandle -> PprStyle -> 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.

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 PprCore

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 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 component id to disambiguate it.

alwaysQualifyNames :: QueryQualifyName Source #

NB: This won't ever show package IDs

withPprStyleDoc :: DynFlags -> PprStyle -> SDoc -> Doc Source #

This is not a recommended way to render SDoc, since it breaks the abstraction layer of SDoc. Prefer to use printSDoc, printSDocLn, bufLeftRenderSDoc, or renderWithStyle instead.

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 :: HasCallStack => String -> SDoc -> a Source #

Throw an exception saying "bug in GHC"

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

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

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

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

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

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 :: HasCallStack => 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 #

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 #