Copyright | Daan Leijen (c) 2000 http://www.cs.uu.nl/~daan Max Bolingbroke (c) 2008 http://blog.omega-prime.co.uk |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Deprecated: Compatibility module for users of ansi-wl-pprint - use Prettyprinter instead
This module is an extended implementation of the functional pretty printer given by Philip Wadler (1997):
"A prettier printer" Draft paper, April 1997, revised March 1998. https://homepages.inf.ed.ac.uk/wadler/papers/prettier/prettier.pdf
In their bare essence, the combinators given by Wadler are not expressive enough to describe some commonly occurring layouts. This library adds new primitives to describe these layouts and works well in practice.
The library is based on a single way to concatenate documents, which is associative and has both a left and right unit. This simple design leads to an efficient and short implementation. The simplicity is reflected in the predictable behaviour of the combinators which make them easy to use in practice.
A thorough description of the primitive combinators and their implementation can be found in Philip Wadler's paper. The main differences with his original paper are:
- The nil document is called
empty
. - The above combinator is called
<$>
. The operator</>
is used for soft line breaks. - There are three new primitives:
align
,fill
andfillBreak
. These are very useful in practice. - There are many additional useful combinators, like
fillSep
andlist
. - There are two renderers:
renderPretty
for pretty printing, andrenderCompact
for quickly rendered, compact output more suitable for generating input to other programs. - The pretty printing algorithm used by
renderPretty
extends the algorithm given by Wadler to take into account a "ribbon width", i.e., a desired maximum number of non-indentation characters to output on any one line. - There are two displayers,
displayS
for strings anddisplayIO
for file-based output. - There is a
Pretty
class. - The implementation uses optimised representations and strictness annotations.
- The library has been extended to allow formatting text for output to ANSI style consoles. New combinators allow control of foreground and background color and the ability to make parts of the text bold or underlined.
Synopsis
- type Doc = Doc AnsiStyle
- empty :: Doc
- char :: Char -> Doc
- text :: String -> Doc
- string :: String -> Doc
- int :: Int -> Doc
- integer :: Integer -> Doc
- float :: Float -> Doc
- double :: Double -> Doc
- rational :: Rational -> Doc
- bool :: Bool -> Doc
- (<>) :: Semigroup a => a -> a -> a
- nest :: Int -> Doc -> Doc
- line :: Doc
- linebreak :: Doc
- group :: Doc -> Doc
- softline :: Doc
- softbreak :: Doc
- hardline :: Doc
- flatAlt :: Doc -> Doc -> Doc
- align :: Doc -> Doc
- hang :: Int -> Doc -> Doc
- indent :: Int -> Doc -> Doc
- encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc
- list :: [Doc] -> Doc
- tupled :: [Doc] -> Doc
- semiBraces :: [Doc] -> Doc
- (<+>) :: Doc -> Doc -> Doc
- (<$>) :: Doc -> Doc -> Doc
- (</>) :: Doc -> Doc -> Doc
- (<$$>) :: Doc -> Doc -> Doc
- (<//>) :: Doc -> Doc -> Doc
- hsep :: [Doc] -> Doc
- vsep :: [Doc] -> Doc
- fillSep :: [Doc] -> Doc
- sep :: [Doc] -> Doc
- hcat :: [Doc] -> Doc
- vcat :: [Doc] -> Doc
- fillCat :: [Doc] -> Doc
- cat :: [Doc] -> Doc
- punctuate :: Doc -> [Doc] -> [Doc]
- fill :: Int -> Doc -> Doc
- fillBreak :: Int -> Doc -> Doc
- enclose :: Doc -> Doc -> Doc -> Doc
- squotes :: Doc -> Doc
- dquotes :: Doc -> Doc
- parens :: Doc -> Doc
- angles :: Doc -> Doc
- braces :: Doc -> Doc
- brackets :: Doc -> Doc
- lparen :: Doc
- rparen :: Doc
- langle :: Doc
- rangle :: Doc
- lbrace :: Doc
- rbrace :: Doc
- lbracket :: Doc
- rbracket :: Doc
- squote :: Doc
- dquote :: Doc
- semi :: Doc
- colon :: Doc
- comma :: Doc
- space :: Doc
- dot :: Doc
- backslash :: Doc
- equals :: Doc
- black :: Doc -> Doc
- red :: Doc -> Doc
- green :: Doc -> Doc
- yellow :: Doc -> Doc
- blue :: Doc -> Doc
- magenta :: Doc -> Doc
- cyan :: Doc -> Doc
- white :: Doc -> Doc
- dullblack :: Doc -> Doc
- dullred :: Doc -> Doc
- dullgreen :: Doc -> Doc
- dullyellow :: Doc -> Doc
- dullblue :: Doc -> Doc
- dullmagenta :: Doc -> Doc
- dullcyan :: Doc -> Doc
- dullwhite :: Doc -> Doc
- onblack :: Doc -> Doc
- onred :: Doc -> Doc
- ongreen :: Doc -> Doc
- onyellow :: Doc -> Doc
- onblue :: Doc -> Doc
- onmagenta :: Doc -> Doc
- oncyan :: Doc -> Doc
- onwhite :: Doc -> Doc
- ondullblack :: Doc -> Doc
- ondullred :: Doc -> Doc
- ondullgreen :: Doc -> Doc
- ondullyellow :: Doc -> Doc
- ondullblue :: Doc -> Doc
- ondullmagenta :: Doc -> Doc
- ondullcyan :: Doc -> Doc
- ondullwhite :: Doc -> Doc
- bold :: Doc -> Doc
- debold :: Doc -> Doc
- underline :: Doc -> Doc
- deunderline :: Doc -> Doc
- plain :: Doc -> Doc
- class Pretty a where
- pretty :: a -> Doc ann
- prettyList :: [a] -> Doc ann
- type SimpleDoc = SimpleDocStream AnsiStyle
- renderPretty :: Float -> Int -> Doc -> SimpleDoc
- renderCompact :: Doc -> SimpleDoc
- renderSmart :: Float -> Int -> Doc -> SimpleDoc
- displayS :: SimpleDoc -> ShowS
- displayIO :: Handle -> SimpleDoc -> IO ()
- putDoc :: Doc -> IO ()
- hPutDoc :: Handle -> Doc -> IO ()
- column :: (Int -> Doc) -> Doc
- columns :: (Maybe Int -> Doc) -> Doc
- nesting :: (Int -> Doc) -> Doc
- width :: Doc -> (Int -> Doc) -> Doc
The algebra of pretty-printing
The combinators in this library satisfy many algebraic laws.
The concatenation operator <>
is associative and has empty
as a left
and right unit:
x <> (y <> z) = (x <> y) <> z x <> empty = x empty <> x = x
The text
combinator is a homomorphism from string concatenation to
document concatenation:
text (s ++ t) = text s <> text t text "" = empty
The char
combinator behaves like one-element text:
char c = text [c]
The nest
combinator is a homomorphism from addition to document
composition. nest
also distributes through document concatenation and is
absorbed by text
and align
:
nest (i + j) x = nest i (nest j x) nest 0 x = x nest i (x <> y) = nest i x <> nest i y nest i empty = empty nest i (text s) = text s nest i (align x) = align x
The group
combinator is absorbed by empty
. group
is commutative with
nest
and align
:
group empty = empty group (text s <> x) = text s <> group x group (nest i x) = nest i (group x) group (align x) = align (group x)
The align
combinator is absorbed by empty
and text
.
align
is idempotent:
align empty = empty align (text s) = text s align (align x) = align x
From the laws of the primitive combinators, we can derive many other laws
for the derived combinators. For example, the above operator <$>
is
defined as:
x <$> y = x <> line <> y
It follows that <$>
is associative and that <$>
and <>
associate
with each other:
x <$> (y <$> z) = (x <$> y) <$> z x <> (y <$> z) = (x <> y) <$> z x <$> (y <> z) = (x <$> y) <> z
Similar laws also hold for the other line break operators </>
, <$$>
,
and <//>
.
Documents
Basic combinators
(<>) :: Semigroup a => a -> a -> a infixr 6 #
An associative operation.
>>>
[1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
Alignment combinators
The combinators in this section cannot be described by Wadler's
original combinators. They align their output relative to the
current output position — in contrast to nest
which always
aligns to the current nesting level. This deprives these
combinators from being `optimal'. In practice however they
prove to be very useful. The combinators in this section should
be used with care, since they are more expensive than the other
combinators. For example, align
shouldn't be used to pretty
print all top-level declarations of a language, but using hang
for let expressions is fine.
semiBraces :: [Doc] -> Doc #
Operators
List combinators
Filler combinators
Bracketing combinators
Named character combinators
ANSI formatting combinators
This terminal formatting functionality is, as far as possible,
portable across platforms with their varying terminals. However,
note that to display ANSI colors and formatting will only be displayed
on Windows consoles if the Doc
value is output using the putDoc
function or one of its friends. Rendering the Doc
to a String
and then outputing that will only work on Unix-style operating systems.
Forecolor combinators
dullyellow :: Doc -> Doc #
dullmagenta :: Doc -> Doc #
Backcolor combinators
ondullblack :: Doc -> Doc #
ondullgreen :: Doc -> Doc #
ondullyellow :: Doc -> Doc #
ondullblue :: Doc -> Doc #
ondullmagenta :: Doc -> Doc #
ondullcyan :: Doc -> Doc #
ondullwhite :: Doc -> Doc #
Emboldening combinators
Underlining combinators
deunderline :: Doc -> Doc #
Formatting elimination combinators
Pretty class
>>>
pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234
prettyList :: [a] -> Doc ann #
is only used to define the prettyList
instance
. In normal circumstances only the Pretty
a => Pretty
[a]
function is used.pretty
>>>
prettyList [1, 23, 456]
[1, 23, 456]
Instances
Pretty Void | Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.
|
Defined in Prettyprinter.Internal | |
Pretty Int16 | |
Defined in Prettyprinter.Internal | |
Pretty Int32 | |
Defined in Prettyprinter.Internal | |
Pretty Int64 | |
Defined in Prettyprinter.Internal | |
Pretty Int8 | |
Defined in Prettyprinter.Internal | |
Pretty Word16 | |
Defined in Prettyprinter.Internal | |
Pretty Word32 | |
Defined in Prettyprinter.Internal | |
Pretty Word64 | |
Defined in Prettyprinter.Internal | |
Pretty Word8 | |
Defined in Prettyprinter.Internal | |
Pretty Text | Automatically converts all newlines to
Note that
Manually use |
Defined in Prettyprinter.Internal | |
Pretty Text | (lazy |
Defined in Prettyprinter.Internal | |
Pretty Integer |
|
Defined in Prettyprinter.Internal | |
Pretty Natural | |
Defined in Prettyprinter.Internal | |
Pretty () |
The argument is not used:
|
Defined in Prettyprinter.Internal | |
Pretty Bool |
|
Defined in Prettyprinter.Internal | |
Pretty Char | Instead of
|
Defined in Prettyprinter.Internal | |
Pretty Double |
|
Defined in Prettyprinter.Internal | |
Pretty Float |
|
Defined in Prettyprinter.Internal | |
Pretty Int |
|
Defined in Prettyprinter.Internal | |
Pretty Word | |
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Identity a) |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (NonEmpty a) | |
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Maybe a) | Ignore
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty [a] |
|
Defined in Prettyprinter.Internal | |
(Pretty a1, Pretty a2) => Pretty (a1, a2) |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Const a b) | |
Defined in Prettyprinter.Internal | |
(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) |
|
Defined in Prettyprinter.Internal |
Rendering and displaying documents
Simple (i.e., rendered) documents
type SimpleDoc = SimpleDocStream AnsiStyle #
renderCompact :: Doc -> SimpleDoc #