Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.Format
Contents
Description
A pretty printer implementation, based loosely on the Wadler-Leijin pretty printer, but redesigned to facilitate a dynamic programming optimal layout algorithm.
This pretty printer module trades some of the generality of the Wadler-Leijin scheme in order to facilitate an efficient optimizing layout engine. The nesting, column, and width combinators are removed.
- data Doc
- data Graphics
- = Options {
- consoleIntensity :: !(Maybe ConsoleIntensity)
- underlining :: !(Maybe Underlining)
- blinkSpeed :: !(Maybe BlinkSpeed)
- foreground :: !(Maybe (Color, ColorIntensity))
- background :: !(Maybe (Color, ColorIntensity))
- swapForegroundBackground :: !(Maybe Bool)
- | Default
- = Options {
- class Format item where
- format :: item -> Doc
- formatList :: [item] -> Doc
- class Monad m => FormatM m item where
- formatM :: item -> m Doc
- formatListM :: [item] -> m Doc
- empty :: Doc
- line :: Doc
- linebreak :: Doc
- hardline :: Doc
- softline :: Doc
- softbreak :: Doc
- char :: Char -> Doc
- string :: String -> Doc
- bytestring :: ByteString -> Doc
- lazyBytestring :: ByteString -> Doc
- lparen :: Doc
- rparen :: Doc
- lbrack :: Doc
- rbrack :: Doc
- lbrace :: Doc
- rbrace :: Doc
- langle :: Doc
- rangle :: Doc
- squote :: Doc
- dquote :: Doc
- backquote :: Doc
- comma :: Doc
- semi :: Doc
- colon :: Doc
- dot :: Doc
- backslash :: Doc
- equals :: Doc
- space :: Doc
- nest :: Int -> Doc -> Doc
- indent :: Int -> Doc -> Doc
- align :: Doc -> Doc
- squoted :: Doc -> Doc
- dquoted :: Doc -> Doc
- parens :: Doc -> Doc
- brackets :: Doc -> Doc
- braces :: Doc -> Doc
- angles :: Doc -> Doc
- list :: [Doc] -> Doc
- graphics :: Graphics -> Doc -> Doc
- dullWhite :: Doc -> Doc
- dullRed :: Doc -> Doc
- dullYellow :: Doc -> Doc
- dullGreen :: Doc -> Doc
- dullBlue :: Doc -> Doc
- dullCyan :: Doc -> Doc
- dullMagenta :: Doc -> Doc
- dullBlack :: Doc -> Doc
- vividWhite :: Doc -> Doc
- vividRed :: Doc -> Doc
- vividYellow :: Doc -> Doc
- vividGreen :: Doc -> Doc
- vividBlue :: Doc -> Doc
- vividCyan :: Doc -> Doc
- vividMagenta :: Doc -> Doc
- vividBlack :: Doc -> Doc
- dullWhiteBackground :: Doc -> Doc
- dullRedBackground :: Doc -> Doc
- dullYellowBackground :: Doc -> Doc
- dullGreenBackground :: Doc -> Doc
- dullBlueBackground :: Doc -> Doc
- dullCyanBackground :: Doc -> Doc
- dullMagentaBackground :: Doc -> Doc
- dullBlackBackground :: Doc -> Doc
- vividWhiteBackground :: Doc -> Doc
- vividRedBackground :: Doc -> Doc
- vividYellowBackground :: Doc -> Doc
- vividGreenBackground :: Doc -> Doc
- vividBlueBackground :: Doc -> Doc
- vividCyanBackground :: Doc -> Doc
- vividMagentaBackground :: Doc -> Doc
- vividBlackBackground :: Doc -> Doc
- beside :: Doc -> Doc -> Doc
- concat :: [Doc] -> Doc
- choose :: [Doc] -> Doc
- (<>) :: Doc -> Doc -> Doc
- (<+>) :: Doc -> Doc -> Doc
- (<!>) :: Doc -> Doc -> Doc
- (<$>) :: Doc -> Doc -> Doc
- (<$$>) :: Doc -> Doc -> Doc
- (</>) :: Doc -> Doc -> Doc
- (<//>) :: Doc -> Doc -> Doc
- hsep :: [Doc] -> Doc
- hcat :: [Doc] -> Doc
- vsep :: [Doc] -> Doc
- vcat :: [Doc] -> Doc
- sep :: [Doc] -> Doc
- cat :: [Doc] -> Doc
- fillSep :: [Doc] -> Doc
- fillCat :: [Doc] -> Doc
- enclose :: Doc -> Doc -> Doc -> Doc
- punctuate :: Doc -> [Doc] -> [Doc]
- encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc
- flatten :: Doc -> Maybe Doc
- group :: Doc -> Doc
- renderOneLine :: Doc -> ByteString
- buildOneLine :: Doc -> Builder
- putOneLine :: Handle -> Doc -> IO ()
- renderFast :: Doc -> ByteString
- buildFast :: Doc -> Builder
- putFast :: Handle -> Doc -> IO ()
- renderOptimal :: Int -> Bool -> Doc -> ByteString
- buildOptimal :: Int -> Bool -> Doc -> Builder
- putOptimal :: Handle -> Int -> Bool -> Doc -> IO ()
Basic Definitions
Types
Graphics options for ANSI terminals. All options are wrapped in
the Maybe
datatype, with Nothing
meaning "leave this option
as-is".
Constructors
Options | Set options on the terminal, or keep the current setting in
the case of |
Fields
| |
Default | Reset the terminal in this mode. |
Type Classes
class Format item where Source
A class representing datatypes that can be formatted as Doc
s.
Minimal complete definition
class Monad m => FormatM m item where Source
A class representing datatypes that can be formatted as Doc
s
inside a monad.
Minimal complete definition
Creating Doc
s
Constructors
Basic
A Doc
consisting of a space character, that can be turned into
a linebreak in order to break lines that are too long.
An empty Doc
that can be turned into a linebreak in order to
break lines that are too long.
From datatypes
bytestring :: ByteString -> Doc Source
Create a Doc
containing a bytestring.
lazyBytestring :: ByteString -> Doc Source
Create a Doc
containing a lazy bytestring
Literals
Derived
Graphics Mode
dullYellow :: Doc -> Doc Source
Color a Doc
dull yellow.
dullMagenta :: Doc -> Doc Source
Color a Doc
dull magenta.
vividWhite :: Doc -> Doc Source
Color a Doc
vivid white.
vividYellow :: Doc -> Doc Source
Color a Doc
vivid yellow.
vividGreen :: Doc -> Doc Source
Color a Doc
vivid green.
vividMagenta :: Doc -> Doc Source
Color a Doc
vivid magenta.
vividBlack :: Doc -> Doc Source
Color a Doc
vivid black.
dullWhiteBackground :: Doc -> Doc Source
Color a Doc
s background dull white.
dullRedBackground :: Doc -> Doc Source
Color a Doc
s background dull red.
dullYellowBackground :: Doc -> Doc Source
Color a Doc
s background dull yellow.
dullGreenBackground :: Doc -> Doc Source
Color a Doc
s background dull green.
dullBlueBackground :: Doc -> Doc Source
Color a Doc
s background dull blue.
dullCyanBackground :: Doc -> Doc Source
Color a Doc
s background dull cyan.
dullMagentaBackground :: Doc -> Doc Source
Color a Doc
s background dull magenta.
dullBlackBackground :: Doc -> Doc Source
Color a Doc
s background dull black.
vividWhiteBackground :: Doc -> Doc Source
Color a Doc
s background vivid white.
vividRedBackground :: Doc -> Doc Source
Color a Doc
s background vivid red.
vividYellowBackground :: Doc -> Doc Source
Color a Doc
s background vivid yellow.
vividGreenBackground :: Doc -> Doc Source
Color a Doc
s background vivid green.
vividBlueBackground :: Doc -> Doc Source
Color a Doc
s background vivid blue.
vividCyanBackground :: Doc -> Doc Source
Color a Doc
s background vivid cyan.
vividMagentaBackground :: Doc -> Doc Source
Color a Doc
s background vivid magenta.
vividBlackBackground :: Doc -> Doc Source
Color a Doc
s background vivid black.
Combining Doc
s
Basic
A choice of several options. Only one of these will be chosen and used to render the final document.
Derived
Transforming Doc
s
flatten :: Doc -> Maybe Doc Source
Erase all linebreaks in a Doc
and replace them with either
spaces or nothing, depending on the kind of linebreak.
Rendering Doc
s
renderOneLine :: Doc -> ByteString Source
Render the entire Doc
to one line. Good for output that
will be read only by a machine, where newlines are not important at all
putOneLine :: Handle -> Doc -> IO () Source
Output the entire Doc
, as rendered by renderOneLine
to the
given Handle
.
renderFast :: Doc -> ByteString Source
Render the entire Doc
, preserving newlines, but without any
indentation. Good for output that will be read only by machine,
but where newlines matter.
putFast :: Handle -> Doc -> IO () Source
Output the entire Doc
, as rendered by renderFast
to the
given Handle
.
Arguments
:: Int | The maximum number of columns. |
-> Bool | Whether or not to render with ANSI terminal options. |
-> Doc | The document to render. |
-> ByteString |
Render a Doc
as a lazy bytestring using an optimal layout
rendering engine. The engine will render the document in the
fewest number of lines possible without exceeding the maximum
column width.