Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- class Outputable a where
- class Outputable a => OutputableBndr a where
- pprBndr :: BindingSite -> a -> SDoc
- pprPrefixOcc, pprInfixOcc :: a -> SDoc
- 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
- empty :: SDoc
- nest :: Int -> SDoc -> SDoc
- char :: Char -> SDoc
- text :: String -> SDoc
- ftext :: FastString -> SDoc
- ptext :: LitString -> SDoc
- ztext :: FastZString -> SDoc
- int :: Int -> SDoc
- intWithCommas :: Integral a => a -> SDoc
- integer :: Integer -> SDoc
- float :: Float -> SDoc
- double :: Double -> SDoc
- rational :: Rational -> 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
- paBrackets :: SDoc -> SDoc
- semi :: SDoc
- comma :: SDoc
- colon :: SDoc
- dcolon :: SDoc
- space :: SDoc
- equals :: SDoc
- dot :: SDoc
- arrow :: SDoc
- darrow :: SDoc
- lparen :: SDoc
- rparen :: SDoc
- lbrack :: SDoc
- rbrack :: SDoc
- lbrace :: SDoc
- rbrace :: SDoc
- underscore :: SDoc
- blankLine :: 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
- punctuate :: SDoc -> [SDoc] -> [SDoc]
- ppWhen :: Bool -> SDoc -> SDoc
- ppUnless :: Bool -> SDoc -> SDoc
- speakNth :: Int -> SDoc
- speakNTimes :: Int -> SDoc
- speakN :: Int -> SDoc
- speakNOf :: Int -> SDoc -> SDoc
- plural :: [a] -> SDoc
- isOrAre :: [a] -> SDoc
- coloured :: PprColour -> SDoc -> SDoc
- data PprColour
- colType :: PprColour
- colCoerc :: PprColour
- colDataCon :: PprColour
- colBinder :: PprColour
- bold :: SDoc -> SDoc
- keyword :: SDoc -> SDoc
- printForC :: DynFlags -> Handle -> SDoc -> IO ()
- printForAsm :: DynFlags -> Handle -> SDoc -> IO ()
- printForUser :: DynFlags -> Handle -> PrintUnqualified -> SDoc -> IO ()
- printForUserPartWay :: DynFlags -> Handle -> Int -> PrintUnqualified -> SDoc -> IO ()
- pprCode :: CodeStyle -> SDoc -> SDoc
- mkCodeStyle :: CodeStyle -> PprStyle
- showSDoc :: DynFlags -> 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
- pprFastFilePath :: FastString -> SDoc
- data BindingSite
- data PprStyle
- data CodeStyle
- type PrintUnqualified = (QueryQualifyName, QueryQualifyModule)
- alwaysQualify :: PrintUnqualified
- alwaysQualifyNames :: QueryQualifyName
- alwaysQualifyModules :: QueryQualifyModule
- neverQualify :: PrintUnqualified
- neverQualifyNames :: QueryQualifyName
- neverQualifyModules :: QueryQualifyModule
- data QualifyName
- sdocWithDynFlags :: (DynFlags -> SDoc) -> SDoc
- sdocWithPlatform :: (Platform -> SDoc) -> SDoc
- getPprStyle :: (PprStyle -> SDoc) -> SDoc
- withPprStyle :: PprStyle -> SDoc -> SDoc
- withPprStyleDoc :: DynFlags -> PprStyle -> SDoc -> Doc
- 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
- ifPprDebug :: SDoc -> SDoc
- qualName :: PprStyle -> QueryQualifyName
- qualModule :: PprStyle -> QueryQualifyModule
- mkErrStyle :: DynFlags -> PrintUnqualified -> PprStyle
- defaultErrStyle :: DynFlags -> PprStyle
- defaultDumpStyle :: PprStyle
- defaultUserStyle :: PprStyle
- mkUserStyle :: PrintUnqualified -> Depth -> PprStyle
- cmdlineParserStyle :: PprStyle
- data Depth
- pprPanic :: String -> SDoc -> a
- pprSorry :: String -> SDoc -> a
- assertPprPanic :: String -> Int -> SDoc -> a
- pprPanicFastInt :: String -> SDoc -> FastInt
- pprPgmError :: String -> SDoc -> a
- pprTrace :: String -> SDoc -> a -> a
- warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a
- trace :: String -> a -> a
- pgmError :: String -> a
- panic :: String -> a
- sorry :: String -> a
- panicFastInt :: String -> FastInt
- assertPanic :: String -> Int -> a
- pprDebugAndThen :: DynFlags -> (String -> a) -> String -> SDoc -> a
Type classes
class Outputable a where Source
Class designating that some type has an SDoc
representation
Nothing
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.
pprBndr :: BindingSite -> a -> SDoc Source
pprPrefixOcc, pprInfixOcc :: a -> SDoc Source
Pretty printing combinators
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
ftext :: FastString -> SDoc Source
ztext :: FastZString -> SDoc Source
intWithCommas :: Integral a => a -> SDoc Source
doubleQuotes :: SDoc -> SDoc Source
angleBrackets :: SDoc -> SDoc Source
paBrackets :: 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
A paragraph-fill combinator. It's much like sep, only it keeps fitting things on one line until it can't fit any more.
speakNth :: Int -> SDoc Source
Converts an integer to a verbal index:
speakNth 1 = text "first" speakNth 5 = text "fifth" speakNth 21 = text "21st"
speakNTimes :: Int -> SDoc Source
Converts a strictly positive integer into a number of times:
speakNTimes 1 = text "once" speakNTimes 2 = text "twice" speakNTimes 4 = text "4 times"
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"
Determines the pluralisation suffix appropriate for the length of a list:
plural [] = char 's' plural ["Hello"] = empty plural ["Hello", "World"] = char 's'
Determines the form of to be appropriate for the length of a list:
isOrAre [] = ptext (sLit "are") isOrAre ["Hello"] = ptext (sLit "is") isOrAre ["Hello", "World"] = ptext (sLit "are")
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
printForUser :: DynFlags -> Handle -> PrintUnqualified -> SDoc -> IO () Source
printForUserPartWay :: DynFlags -> Handle -> Int -> PrintUnqualified -> SDoc -> IO () Source
mkCodeStyle :: CodeStyle -> PprStyle Source
showSDocOneLine :: DynFlags -> SDoc -> String Source
showSDocForUser :: DynFlags -> PrintUnqualified -> SDoc -> String Source
showSDocDebug :: DynFlags -> SDoc -> String Source
showSDocDump :: DynFlags -> SDoc -> String Source
showSDocDumpOneLine :: DynFlags -> SDoc -> String Source
showSDocUnqual :: DynFlags -> SDoc -> String Source
showPpr :: Outputable a => DynFlags -> a -> String Source
pprInfixVar :: Bool -> SDoc -> SDoc Source
pprPrefixVar :: Bool -> SDoc -> SDoc Source
pprHsString :: FastString -> SDoc Source
Special combinator for showing string literals.
pprHsBytes :: ByteString -> SDoc Source
Special combinator for showing string literals.
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.
type PrintUnqualified = (QueryQualifyName, QueryQualifyModule) Source
alwaysQualifyNames :: QueryQualifyName Source
alwaysQualifyModules :: QueryQualifyModule Source
neverQualifyNames :: QueryQualifyName Source
neverQualifyModules :: QueryQualifyModule Source
sdocWithDynFlags :: (DynFlags -> SDoc) -> SDoc Source
sdocWithPlatform :: (Platform -> SDoc) -> SDoc Source
getPprStyle :: (PprStyle -> SDoc) -> SDoc Source
withPprStyle :: PprStyle -> SDoc -> SDoc Source
pprSetDepth :: Depth -> SDoc -> SDoc Source
debugStyle :: PprStyle -> Bool Source
ifPprDebug :: SDoc -> SDoc Source
qualModule :: PprStyle -> QueryQualifyModule Source
mkErrStyle :: DynFlags -> PrintUnqualified -> PprStyle Source
Style for printing error messages
mkUserStyle :: PrintUnqualified -> Depth -> PprStyle Source
Error handling and debugging utilities
assertPprPanic :: 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
pprPanicFastInt :: String -> SDoc -> FastInt Source
Specialization of pprPanic that can be safely used with FastInt
pprPgmError :: String -> SDoc -> a Source
Throw an exception saying "bug in pgm being compiled" (used for unusual program errors)
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
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.
panicFastInt :: String -> FastInt Source
Panic while pretending to return an unboxed int. You can't use the regular panic functions in expressions producing unboxed ints because they have the wrong kind.
assertPanic :: String -> Int -> a Source
Throw an failed assertion exception for a given filename and line number.