| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- class Outputable a where
- class Outputable a => OutputableBndr a where- pprBndr :: BindingSite -> a -> SDoc
- pprPrefixOcc, pprInfixOcc :: a -> SDoc
- bndrIsJoin_maybe :: a -> Maybe Int
 
- data SDoc
- runSDoc :: SDoc -> SDocContext -> Doc
- initSDocContext :: DynFlags -> PprStyle -> SDocContext
- docToSDoc :: Doc -> SDoc
- interppSP :: Outputable a => [a] -> SDoc
- interpp'SP :: Outputable a => [a] -> SDoc
- pprQuotedList :: Outputable a => [a] -> SDoc
- pprWithCommas :: (a -> SDoc) -> [a] -> SDoc
- quotedListWithOr :: [SDoc] -> SDoc
- quotedListWithNor :: [SDoc] -> SDoc
- pprWithBars :: (a -> SDoc) -> [a] -> SDoc
- empty :: SDoc
- isEmpty :: DynFlags -> SDoc -> Bool
- nest :: Int -> SDoc -> SDoc
- char :: Char -> SDoc
- text :: String -> SDoc
- ftext :: FastString -> SDoc
- ptext :: PtrString -> SDoc
- ztext :: FastZString -> SDoc
- int :: Int -> SDoc
- intWithCommas :: Integral a => a -> SDoc
- integer :: Integer -> SDoc
- word :: Integer -> SDoc
- float :: Float -> SDoc
- double :: Double -> SDoc
- rational :: Rational -> SDoc
- doublePrec :: Int -> Double -> SDoc
- parens :: SDoc -> SDoc
- cparen :: Bool -> SDoc -> SDoc
- brackets :: SDoc -> SDoc
- braces :: SDoc -> SDoc
- quotes :: SDoc -> SDoc
- quote :: SDoc -> SDoc
- doubleQuotes :: SDoc -> SDoc
- angleBrackets :: SDoc -> SDoc
- semi :: SDoc
- comma :: SDoc
- colon :: SDoc
- dcolon :: SDoc
- space :: SDoc
- equals :: SDoc
- dot :: SDoc
- vbar :: SDoc
- arrow :: SDoc
- larrow :: SDoc
- darrow :: SDoc
- arrowt :: SDoc
- larrowt :: SDoc
- arrowtt :: SDoc
- larrowtt :: SDoc
- lparen :: SDoc
- rparen :: SDoc
- lbrack :: SDoc
- rbrack :: SDoc
- lbrace :: SDoc
- rbrace :: SDoc
- underscore :: SDoc
- blankLine :: SDoc
- forAllLit :: SDoc
- kindType :: SDoc
- bullet :: SDoc
- (<>) :: SDoc -> SDoc -> SDoc
- (<+>) :: SDoc -> SDoc -> SDoc
- hcat :: [SDoc] -> SDoc
- hsep :: [SDoc] -> SDoc
- ($$) :: SDoc -> SDoc -> SDoc
- ($+$) :: SDoc -> SDoc -> SDoc
- vcat :: [SDoc] -> SDoc
- sep :: [SDoc] -> SDoc
- cat :: [SDoc] -> SDoc
- fsep :: [SDoc] -> SDoc
- fcat :: [SDoc] -> SDoc
- hang :: SDoc -> Int -> SDoc -> SDoc
- hangNotEmpty :: SDoc -> Int -> SDoc -> SDoc
- punctuate :: SDoc -> [SDoc] -> [SDoc]
- ppWhen :: Bool -> SDoc -> SDoc
- ppUnless :: Bool -> SDoc -> SDoc
- speakNth :: Int -> SDoc
- speakN :: Int -> SDoc
- speakNOf :: Int -> SDoc -> SDoc
- plural :: [a] -> SDoc
- isOrAre :: [a] -> SDoc
- doOrDoes :: [a] -> SDoc
- unicodeSyntax :: SDoc -> SDoc -> SDoc
- coloured :: PprColour -> SDoc -> SDoc
- keyword :: SDoc -> SDoc
- printSDoc :: Mode -> DynFlags -> Handle -> PprStyle -> SDoc -> IO ()
- printSDocLn :: Mode -> DynFlags -> Handle -> PprStyle -> SDoc -> IO ()
- printForUser :: DynFlags -> Handle -> PrintUnqualified -> SDoc -> IO ()
- printForUserPartWay :: DynFlags -> Handle -> Int -> PrintUnqualified -> SDoc -> IO ()
- printForC :: DynFlags -> Handle -> SDoc -> IO ()
- bufLeftRenderSDoc :: DynFlags -> BufHandle -> PprStyle -> SDoc -> IO ()
- pprCode :: CodeStyle -> SDoc -> SDoc
- mkCodeStyle :: CodeStyle -> PprStyle
- showSDoc :: DynFlags -> SDoc -> String
- showSDocUnsafe :: SDoc -> String
- showSDocOneLine :: DynFlags -> SDoc -> String
- showSDocForUser :: DynFlags -> PrintUnqualified -> SDoc -> String
- showSDocDebug :: DynFlags -> SDoc -> String
- showSDocDump :: DynFlags -> SDoc -> String
- showSDocDumpOneLine :: DynFlags -> SDoc -> String
- showSDocUnqual :: DynFlags -> SDoc -> String
- showPpr :: Outputable a => DynFlags -> a -> String
- renderWithStyle :: DynFlags -> SDoc -> PprStyle -> String
- pprInfixVar :: Bool -> SDoc -> SDoc
- pprPrefixVar :: Bool -> SDoc -> SDoc
- pprHsChar :: Char -> SDoc
- pprHsString :: FastString -> SDoc
- pprHsBytes :: ByteString -> SDoc
- primFloatSuffix :: SDoc
- primCharSuffix :: SDoc
- primWordSuffix :: SDoc
- primDoubleSuffix :: SDoc
- primInt64Suffix :: SDoc
- primWord64Suffix :: SDoc
- primIntSuffix :: SDoc
- pprPrimChar :: Char -> SDoc
- pprPrimInt :: Integer -> SDoc
- pprPrimWord :: Integer -> SDoc
- pprPrimInt64 :: Integer -> SDoc
- pprPrimWord64 :: Integer -> SDoc
- pprFastFilePath :: FastString -> SDoc
- data BindingSite
- data PprStyle
- data CodeStyle
- data PrintUnqualified = QueryQualify {}
- type QueryQualifyName = Module -> OccName -> QualifyName
- type QueryQualifyModule = Module -> Bool
- type QueryQualifyPackage = UnitId -> Bool
- reallyAlwaysQualify :: PrintUnqualified
- reallyAlwaysQualifyNames :: QueryQualifyName
- alwaysQualify :: PrintUnqualified
- alwaysQualifyNames :: QueryQualifyName
- alwaysQualifyModules :: QueryQualifyModule
- neverQualify :: PrintUnqualified
- neverQualifyNames :: QueryQualifyName
- neverQualifyModules :: QueryQualifyModule
- alwaysQualifyPackages :: QueryQualifyPackage
- neverQualifyPackages :: QueryQualifyPackage
- data QualifyName
- queryQual :: PprStyle -> PrintUnqualified
- sdocWithDynFlags :: (DynFlags -> SDoc) -> SDoc
- sdocWithPlatform :: (Platform -> SDoc) -> SDoc
- updSDocDynFlags :: (DynFlags -> DynFlags) -> SDoc -> SDoc
- getPprStyle :: (PprStyle -> SDoc) -> SDoc
- withPprStyle :: PprStyle -> SDoc -> SDoc
- withPprStyleDoc :: DynFlags -> PprStyle -> SDoc -> Doc
- setStyleColoured :: Bool -> PprStyle -> PprStyle
- pprDeeper :: SDoc -> SDoc
- pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc
- pprSetDepth :: Depth -> SDoc -> SDoc
- codeStyle :: PprStyle -> Bool
- userStyle :: PprStyle -> Bool
- debugStyle :: PprStyle -> Bool
- dumpStyle :: PprStyle -> Bool
- asmStyle :: PprStyle -> Bool
- qualName :: PprStyle -> QueryQualifyName
- qualModule :: PprStyle -> QueryQualifyModule
- qualPackage :: PprStyle -> QueryQualifyPackage
- mkErrStyle :: DynFlags -> PrintUnqualified -> PprStyle
- defaultErrStyle :: DynFlags -> PprStyle
- defaultDumpStyle :: DynFlags -> PprStyle
- mkDumpStyle :: DynFlags -> PrintUnqualified -> PprStyle
- defaultUserStyle :: DynFlags -> PprStyle
- mkUserStyle :: DynFlags -> PrintUnqualified -> Depth -> PprStyle
- cmdlineParserStyle :: DynFlags -> PprStyle
- data Depth
- ifPprDebug :: SDoc -> SDoc -> SDoc
- whenPprDebug :: SDoc -> SDoc
- getPprDebug :: (Bool -> SDoc) -> SDoc
- pprPanic :: HasCallStack => String -> SDoc -> a
- pprSorry :: String -> SDoc -> a
- assertPprPanic :: HasCallStack => String -> Int -> SDoc -> a
- pprPgmError :: String -> SDoc -> a
- pprTrace :: String -> SDoc -> a -> a
- pprTraceDebug :: String -> SDoc -> a -> a
- pprTraceIt :: Outputable a => String -> a -> a
- warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a
- pprSTrace :: HasCallStack => SDoc -> a -> a
- pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a
- pprTraceM :: Applicative f => String -> SDoc -> f ()
- trace :: String -> a -> a
- pgmError :: String -> a
- panic :: String -> a
- sorry :: String -> a
- assertPanic :: String -> Int -> a
- pprDebugAndThen :: DynFlags -> (String -> a) -> SDoc -> SDoc -> a
- callStackDoc :: HasCallStack => SDoc
Type classes
class Outputable a where Source #
Class designating that some type has an SDoc representation
Minimal complete definition
Nothing
Instances
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
Methods
pprBndr :: BindingSite -> a -> SDoc Source #
pprPrefixOcc :: a -> SDoc Source #
pprInfixOcc :: a -> SDoc Source #
bndrIsJoin_maybe :: a -> Maybe Int Source #
Instances
Pretty printing combinators
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
| IsString SDoc Source # | |
| Defined in Outputable Methods fromString :: String -> SDoc # | |
initSDocContext :: DynFlags -> PprStyle -> SDocContext 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'
quotedListWithOr :: [SDoc] -> SDoc Source #
quotedListWithNor :: [SDoc] -> SDoc Source #
ftext :: FastString -> SDoc Source #
ztext :: FastZString -> SDoc Source #
intWithCommas :: Integral a => a -> SDoc Source #
doublePrec :: Int -> Double -> SDoc Source #
doublePrec p n shows a floating point number n with p
 digits of precision after the decimal point.
doubleQuotes :: SDoc -> SDoc Source #
angleBrackets :: SDoc -> SDoc Source #
underscore :: SDoc Source #
($$) :: SDoc -> SDoc -> SDoc Source #
Join two SDoc together vertically; if there is
 no vertical overlap it "dovetails" the two onto one line
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.
hangNotEmpty :: SDoc -> Int -> SDoc -> SDoc Source #
This behaves like hang, but does not indent the second document
 when the header is empty.
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
printSDocLn :: Mode -> DynFlags -> Handle -> PprStyle -> SDoc -> IO () Source #
Like printSDoc but appends an extra newline.
printForUser :: DynFlags -> Handle -> PrintUnqualified -> SDoc -> IO () Source #
printForUserPartWay :: DynFlags -> Handle -> Int -> PrintUnqualified -> SDoc -> IO () Source #
printForC :: DynFlags -> Handle -> SDoc -> IO () Source #
Like printSDocLn but specialized with LeftMode and
 PprCode CStyle
mkCodeStyle :: CodeStyle -> PprStyle Source #
showSDocUnsafe :: SDoc -> String Source #
showSDocForUser :: DynFlags -> PrintUnqualified -> SDoc -> String Source #
pprHsString :: FastString -> SDoc Source #
Special combinator for showing string literals.
pprHsBytes :: ByteString -> SDoc Source #
Special combinator for showing bytestring literals.
primIntSuffix :: SDoc Source #
pprPrimChar :: Char -> SDoc Source #
Special combinator for showing unboxed literals.
pprPrimInt :: Integer -> SDoc Source #
pprPrimWord :: Integer -> SDoc Source #
pprPrimInt64 :: Integer -> SDoc Source #
pprPrimWord64 :: Integer -> SDoc Source #
pprFastFilePath :: FastString -> SDoc Source #
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 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.
Constructors
| QueryQualify | |
type QueryQualifyName = Module -> OccName -> QualifyName Source #
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
data QualifyName Source #
Constructors
| NameUnqual | |
| NameQual ModuleName | |
| NameNotInScope1 | |
| NameNotInScope2 | 
Instances
| Outputable QualifyName Source # | |
| Defined in Outputable | |
queryQual :: PprStyle -> PrintUnqualified Source #
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.
debugStyle :: PprStyle -> Bool Source #
qualName :: PprStyle -> QueryQualifyName Source #
mkErrStyle :: DynFlags -> PrintUnqualified -> PprStyle Source #
Style for printing error messages
defaultErrStyle :: DynFlags -> PprStyle Source #
defaultDumpStyle :: DynFlags -> PprStyle Source #
mkDumpStyle :: DynFlags -> PrintUnqualified -> PprStyle Source #
defaultUserStyle :: DynFlags -> PprStyle Source #
mkUserStyle :: DynFlags -> PrintUnqualified -> Depth -> PprStyle Source #
whenPprDebug :: SDoc -> SDoc Source #
Says what to do with -dppr-debug; without, return empty
Error handling and debugging utilities
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)
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.
pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a Source #
pprTraceException desc x action runs action, printing a message
 if it throws an exception.
The trace function outputs the trace message given as its first argument,
before returning the second argument as its result.
For example, this returns the value of f x but first outputs the message.
>>>let x = 123; f = show>>>trace ("calling f with x = " ++ show x) (f x)"calling f with x = 123 123"
The trace function should only be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
that it is a pure function but it has the side effect of outputting the
trace message.
assertPanic :: String -> Int -> a Source #
Throw a failed assertion exception for a given filename and line number.
callStackDoc :: HasCallStack => SDoc Source #