Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- 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
- empty :: SDoc
- isEmpty :: DynFlags -> SDoc -> Bool
- 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
- 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
- paBrackets :: 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
- (<>) :: 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
- 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
- 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
- primDoubleSuffix :: 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
- 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
- qualPackage :: PprStyle -> QueryQualifyPackage
- mkErrStyle :: DynFlags -> PrintUnqualified -> PprStyle
- defaultErrStyle :: DynFlags -> PprStyle
- defaultDumpStyle :: PprStyle
- mkDumpStyle :: PrintUnqualified -> PprStyle
- defaultUserStyle :: PprStyle
- mkUserStyle :: PrintUnqualified -> Depth -> PprStyle
- cmdlineParserStyle :: PprStyle
- data Depth
- pprPanic :: String -> SDoc -> a
- pprSorry :: String -> SDoc -> a
- assertPprPanic :: (?callStack :: CallStack) => String -> Int -> SDoc -> a
- pprPgmError :: String -> SDoc -> a
- pprTrace :: String -> SDoc -> a -> a
- pprTraceIt :: Outputable a => String -> a -> a
- warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a
- pprSTrace :: (?callStack :: CallStack) => SDoc -> a -> a
- trace :: String -> a -> a
- pgmError :: String -> a
- panic :: String -> a
- sorry :: String -> a
- assertPanic :: String -> Int -> a
- pprDebugAndThen :: DynFlags -> (String -> a) -> SDoc -> SDoc -> a
Type classes
class Outputable a where Source #
Class designating that some type has an SDoc
representation
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 #
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 #
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
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
printForUser :: DynFlags -> Handle -> PrintUnqualified -> SDoc -> IO () Source #
printForUserPartWay :: DynFlags -> Handle -> Int -> PrintUnqualified -> SDoc -> IO () Source #
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.
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.
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
queryQual :: PprStyle -> PrintUnqualified Source #
pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc Source #
Truncate a list that is longer than the current depth.
debugStyle :: PprStyle -> Bool Source #
ifPprDebug :: SDoc -> SDoc Source #
qualName :: PprStyle -> QueryQualifyName Source #
mkErrStyle :: DynFlags -> PrintUnqualified -> PprStyle Source #
Style for printing error messages
defaultErrStyle :: DynFlags -> PprStyle Source #
mkUserStyle :: PrintUnqualified -> Depth -> PprStyle Source #
Error handling and debugging utilities
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)
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.
assertPanic :: String -> Int -> a Source #
Throw an failed assertion exception for a given filename and line number.