| Copyright | Daan Leijen (c) 2000 http://www.cs.uu.nl/~daan Max Bolingbroke (c) 2008 http://blog.omega-prime.co.uk David Luposchainsky (c) 2016 http://github.com/quchen | 
|---|---|
| License | BSD-style (see the file LICENSE.md) | 
| Maintainer | David Luposchainsky <dluposchainsky (λ) google> | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Data.Text.Prettyprint.Doc
Contents
Description
Overview
This module defines a prettyprinter to format text in a flexible and
 convenient way. The idea is to combine a Document out of many small
 components, then using a layouter to convert it to an easily renderable
 SimpleDocStream, which can then be rendered to a variety of formats, for
 example plain Text.
The documentation consists of several parts:
- Just below is some general information about the library.
- The actual library with extensive documentation and examples
- Migration guide for users familiar with (ansi-)wl-pprint
Starting out
As a reading list for starters, some of the most commonly used functions in
 this module include <>, hsep, <+>, vsep, align, hang. These cover
 many use cases already, and many other functions are variations or
 combinations of these.
Simple example
Let’s prettyprint a simple Haskell type definition. First, intersperse ->
 and add a leading ::,
>>>let prettyType = align . sep . zipWith (<+>) ("::" : repeat "->")
The sep function is one way of concatenating documents, there are multiple
 others, e.g. vsep, cat and fillSep. In our case, sep space-separates
 all entries if there is space, and newlines if the remaining line is too
 short.
Second, prepend the name to the type,
>>>let prettyDecl n tys = pretty n <+> prettyType tys
Now we can define a document that contains some type signature:
>>>let doc = prettyDecl "example" ["Int", "Bool", "Char", "IO ()"]
This document can now be printed, and it automatically adapts to available space. If the page is wide enough (80 characters in this case), the definitions are space-separated,
>>>putDocW 80 docexample :: Int -> Bool -> Char -> IO ()
If we narrow the page width to only 20 characters, the same document renders vertically aligned:
>>>putDocW 20 docexample :: Int -> Bool -> Char -> IO ()
Speaking of alignment, had we not used align, the -> would be at the
 beginning of each line, and not beneath the ::.
General workflow
╔══════════╗ ║ ║ ╭────────────────────╮ ║ ║ │vsep,pretty,<+>, │ ║ ║ │nest,align, … │ ║ ║ ╰─────────┬──────────╯ ║ ║ │ ║ Create ║ │ ║ ║ │ ║ ║ ▽ ║ ║ ╭───────────────────╮ ║ ║ │Doc│ ╠══════════╣ │ (rich document) │ ║ ║ ╰─────────┬─────────╯ ║ ║ │ ║ ║ │ Layout algorithms ║ Layout ║ │ e.g.layoutPretty║ ║ ▽ ║ ║ ╭───────────────────╮ ║ ║ │SimpleDocStream│ ╠══════════╣ │ (simple document) │ ║ ║ ╰─────────┬─────────╯ ║ ║ │ ║ ║ ├─────────────────────────────╮ ║ ║ │ │treeForm║ ║ │ ▽ ║ ║ │ ╭───────────────╮ ║ ║ │ │SimpleDocTree│ ║ Render ║ │ ╰───────┬───────╯ ║ ║ │ │ ║ ║ ╭───────────────────┼─────────────────╮ ╭────────┴────────╮ ║ ║ │ │ │ │ │ ║ ║ ▽ ▽ ▽ ▽ ▽ ║ ║ ╭───────────────╮ ╭───────────────╮ ╭───────────────╮ ╭───────────────╮ ║ ║ │ ANSI terminal │ │ PlainText│ │ other/custom │ │ HTML │ ║ ║ ╰───────────────╯ ╰───────────────╯ ╰───────────────╯ ╰───────────────╯ ║ ║ ╚══════════╝
How the layout works
There are two key concepts to laying a document out: the available width, and
 grouping.
Available width
The page has a certain maximum width, which the layouter tries to not exceed,
 by inserting line breaks where possible. The functions given in this module
 make it fairly straightforward to specify where, and under what
 circumstances, such a line break may be inserted by the layouter, for example
 via the sep function.
There is also the concept of ribbon width. The ribbon is the part of a line
 that is printed, i.e. the line length without the leading indentation. The
 layouters take a ribbon fraction argument, which specifies how much of a line
 should be filled before trying to break it up. A ribbon width of 0.5 in a
 document of width 80 will result in the layouter to try to not exceed 0.5*80 =
 40 (ignoring current indentation depth).
Grouping
A document can be grouped, which tells the layouter that it should attempt
 to collapse it to a single line. If the result does not fit within the
 constraints (given by page and ribbon widths), the document is rendered
 unaltered. This allows fallback definitions, so that we get nice results even
 when the original document would exceed the layout constraints.
Things the prettyprinter cannot do
Due to how the Wadler/Leijen algorithm is designed, a couple of things are unsupported right now, with a high possibility of having no sensible implementation without significantly changing the layout algorithm. In particular, this includes
- Leading symbols instead of just spaces for indentation, as used by the
     Linux treetool for example
- Multi-column layouts, in particular tables with multiple cells of equal width adjacent to each other
Some helpful tips
Which kind of annotation should I use?
Summary: Use semantic annotations for Doc
For example, suppose you want to prettyprint some programming language code.
 If you want keywords to be red, you should annotate the DocKeyword field (without any notion of color), and then after
 layouting convert the annotations to map KeywordRedreAnnotateSDocRed.
While both versions would superficially work equally well and would create identical output, the recommended way has two significant advantages: modularity and extensibility.
Modularity: To change the color of keywords later, you have to touch one
 point, namely the mapping in reAnnotateSKeywordRed. If you have 'annotate Red …' everywher, you’ll have to do a full
 text replacement, producing a large diff and touching lots of places for a
 very small change.
Extensibility: Adding a different backend in the recommended version is
 simply adding another reAnnotateSDocRedDoc
Synopsis
- data Doc ann
- class Pretty a where
- viaShow :: Show a => a -> Doc ann
- unsafeViaShow :: Show a => a -> Doc ann
- emptyDoc :: Doc ann
- nest :: Int -> Doc ann -> Doc ann
- line :: Doc ann
- line' :: Doc ann
- softline :: Doc ann
- softline' :: Doc ann
- hardline :: Doc ann
- group :: Doc ann -> Doc ann
- flatAlt :: Doc ann -> Doc ann -> Doc ann
- align :: Doc ann -> Doc ann
- hang :: Int -> Doc ann -> Doc ann
- indent :: Int -> Doc ann -> Doc ann
- encloseSep :: Doc ann -> Doc ann -> Doc ann -> [Doc ann] -> Doc ann
- list :: [Doc ann] -> Doc ann
- tupled :: [Doc ann] -> Doc ann
- (<>) :: Semigroup a => a -> a -> a
- (<+>) :: Doc ann -> Doc ann -> Doc ann
- concatWith :: Foldable t => (Doc ann -> Doc ann -> Doc ann) -> t (Doc ann) -> Doc ann
- hsep :: [Doc ann] -> Doc ann
- vsep :: [Doc ann] -> Doc ann
- fillSep :: [Doc ann] -> Doc ann
- sep :: [Doc ann] -> Doc ann
- hcat :: [Doc ann] -> Doc ann
- vcat :: [Doc ann] -> Doc ann
- fillCat :: [Doc ann] -> Doc ann
- cat :: [Doc ann] -> Doc ann
- punctuate :: Doc ann -> [Doc ann] -> [Doc ann]
- column :: (Int -> Doc ann) -> Doc ann
- nesting :: (Int -> Doc ann) -> Doc ann
- width :: Doc ann -> (Int -> Doc ann) -> Doc ann
- pageWidth :: (PageWidth -> Doc ann) -> Doc ann
- fill :: Int -> Doc ann -> Doc ann
- fillBreak :: Int -> Doc ann -> Doc ann
- plural :: (Num amount, Eq amount) => doc -> doc -> amount -> doc
- enclose :: Doc ann -> Doc ann -> Doc ann -> Doc ann
- surround :: Doc ann -> Doc ann -> Doc ann -> Doc ann
- squotes :: Doc ann -> Doc ann
- dquotes :: Doc ann -> Doc ann
- parens :: Doc ann -> Doc ann
- angles :: Doc ann -> Doc ann
- brackets :: Doc ann -> Doc ann
- braces :: Doc ann -> Doc ann
- lparen :: Doc ann
- rparen :: Doc ann
- langle :: Doc ann
- rangle :: Doc ann
- lbrace :: Doc ann
- rbrace :: Doc ann
- lbracket :: Doc ann
- rbracket :: Doc ann
- squote :: Doc ann
- dquote :: Doc ann
- semi :: Doc ann
- colon :: Doc ann
- comma :: Doc ann
- space :: Doc ann
- dot :: Doc ann
- slash :: Doc ann
- backslash :: Doc ann
- equals :: Doc ann
- pipe :: Doc ann
- annotate :: ann -> Doc ann -> Doc ann
- unAnnotate :: Doc ann -> Doc xxx
- reAnnotate :: (ann -> ann') -> Doc ann -> Doc ann'
- alterAnnotations :: (ann -> [ann']) -> Doc ann -> Doc ann'
- unAnnotateS :: SimpleDocStream ann -> SimpleDocStream xxx
- reAnnotateS :: (ann -> ann') -> SimpleDocStream ann -> SimpleDocStream ann'
- alterAnnotationsS :: (ann -> Maybe ann') -> SimpleDocStream ann -> SimpleDocStream ann'
- fuse :: FusionDepth -> Doc ann -> Doc ann
- data FusionDepth
- data SimpleDocStream ann- = SFail
- | SEmpty
- | SChar Char (SimpleDocStream ann)
- | SText !Int Text (SimpleDocStream ann)
- | SLine !Int (SimpleDocStream ann)
- | SAnnPush ann (SimpleDocStream ann)
- | SAnnPop (SimpleDocStream ann)
 
- data PageWidth
- newtype LayoutOptions = LayoutOptions {}
- defaultLayoutOptions :: LayoutOptions
- layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann
- layoutCompact :: Doc ann -> SimpleDocStream ann
- layoutSmart :: LayoutOptions -> Doc ann -> SimpleDocStream ann
- removeTrailingWhitespace :: SimpleDocStream ann -> SimpleDocStream ann
Documents
The abstract data type Doc annann.
More specifically, a value of type Doc
The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as
- color information (e.g. when rendering to the terminal)
- mouseover text (e.g. when rendering to rich HTML)
- whether to show something or not (to allow simple or detailed versions)
The simplest way to display a Doc is via the Show class.
>>>putStrLn (show (vsep ["hello", "world"]))hello world
Instances
Basic functionality
Minimal complete definition
Methods
pretty :: a -> Doc ann Source #
>>>pretty 1 <+> pretty "hello" <+> pretty 1.2341 hello 1.234
pretty :: Show a => a -> Doc ann Source #
>>>pretty 1 <+> pretty "hello" <+> pretty 1.2341 hello 1.234
prettyList :: [a] -> Doc ann Source #
prettyListinstance
 . In normal circumstances only the Pretty a => Pretty [a]pretty
>>>prettyList [1, 23, 456][1, 23, 456]
Instances
| Pretty Bool Source # | 
 | 
| Pretty Char Source # | Instead of  
 | 
| Pretty Double Source # | 
 | 
| Pretty Float Source # | 
 | 
| Pretty Int Source # | 
 | 
| Pretty Int8 Source # | |
| Pretty Int16 Source # | |
| Pretty Int32 Source # | |
| Pretty Int64 Source # | |
| Pretty Integer Source # | 
 | 
| Pretty Natural Source # | |
| Pretty Word Source # | |
| Pretty Word8 Source # | |
| Pretty Word16 Source # | |
| Pretty Word32 Source # | |
| Pretty Word64 Source # | |
| Pretty () Source # | 
 The argument is not used, 
 | 
| Defined in Data.Text.Prettyprint.Doc.Internal | |
| Pretty Void Source # | 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. 
 | 
| Pretty Text Source # | (lazy  | 
| Pretty Text Source # | Automatically converts all newlines to  
 Note that   
 Manually use  | 
| Pretty a => Pretty [a] Source # | 
 | 
| Defined in Data.Text.Prettyprint.Doc.Internal | |
| Pretty a => Pretty (Maybe a) Source # | Ignore  
 
 | 
| Pretty a => Pretty (Identity a) Source # | 
 | 
| Pretty a => Pretty (NonEmpty a) Source # | |
| (Pretty a1, Pretty a2) => Pretty (a1, a2) Source # | 
 | 
| Defined in Data.Text.Prettyprint.Doc.Internal | |
| (Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) Source # | 
 | 
| Defined in Data.Text.Prettyprint.Doc.Internal | |
| Pretty a => Pretty (Const a b) Source # | |
viaShow :: Show a => a -> Doc ann Source #
Convenience function to convert a Showable value to a Doc. If the
 String does not contain newlines, consider using the more performant
 unsafeViaShow.
unsafeViaShow :: Show a => a -> Doc ann Source #
softline behaves like spaceline
Here, we have enough space to put everything in one line:
>>>let doc = "lorem ipsum" <> softline <> "dolor sit amet">>>putDocW 80 doclorem ipsum dolor sit amet
If we narrow the page to width 10, the layouter produces a line break:
>>>putDocW 10 doclorem ipsum dolor sit amet
softline=groupline
softline'softlinememptyspacelineline'softlinesoftline'
With enough space, we get direct concatenation:
>>>let doc = "ThisWord" <> softline' <> "IsWayTooLong">>>putDocW 80 docThisWordIsWayTooLong
If we narrow the page to width 10, the layouter produces a line break:
>>>putDocW 10 docThisWord IsWayTooLong
softline'=groupline'
A hardlinegrouped or
 when there is plenty of space. Note that it might still be simply discarded
 if it is part of a flatAlt inside a group.
>>>let doc = "lorem ipsum" <> hardline <> "dolor sit amet">>>putDocW 1000 doclorem ipsum dolor sit amet
>>>group doclorem ipsum dolor sit amet
group :: Doc ann -> Doc ann Source #
( tries laying out group x)x into a single line by removing the
 contained line breaks; if this does not fit the page, x is laid out without
 any changes. The group function is key to layouts that adapt to available
 space nicely.
See vcat, line, or flatAlt for examples that are related, or make good
 use of it.
( renders as flatAlt x fallback)x by default, but falls back to
 fallback when grouped. Since the layout algorithms rely on group having
 an effect of shortening the width of the contained text, careless usage of
 flatAlt with wide fallbacks might lead to unappealingly long lines.
flatAlt is particularly useful for defining conditional separators such as
softHyphen =flatAltmempty"-" softline =flatAltspaceline
We can use this to render Haskell's do-notation nicely:
>>>let open = flatAlt "" "{ ">>>let close = flatAlt "" " }">>>let separator = flatAlt "" "; ">>>let prettyDo xs = group ("do" <+> align (encloseSep open close separator xs))>>>let statements = ["name:_ <- getArgs", "let greet = \"Hello, \" <> name", "putStrLn greet"]
This is put into a single line with {;} style if it fits,
>>>putDocW 80 (prettyDo statements)do { name:_ <- getArgs; let greet = "Hello, " <> name; putStrLn greet }
When there is not enough space the statements are broken up into lines nicely,
>>>putDocW 10 (prettyDo statements)do name:_ <- getArgs let greet = "Hello, " <> name putStrLn greet
Alignment functions
The functions in this section cannot be described by Wadler's original
 functions. They align their output relative to the current output
 position - in contrast to nestalignhang
align :: Doc ann -> Doc ann Source #
( lays out the document align x)x with the nesting level set to the
 current column. It is used for example to implement hang.
As an example, we will put a document right above another one, regardless of
 the current nesting level. Without alignment, the second line is put simply
 below everything we've had so far,
>>>"lorem" <+> vsep ["ipsum", "dolor"]lorem ipsum dolor
If we add an align to the mix, the vsep
>>>"lorem" <+> align (vsep ["ipsum", "dolor"])lorem ipsum dolor
Arguments
| :: Int | Change of nesting level, relative to the start of the first line | 
| -> Doc ann | |
| -> Doc ann | 
( lays out the document hang i x)x with a nesting level set to the
 current column plus i. Negative values are allowed, and decrease the
 nesting level accordingly.
>>>let doc = reflow "Indenting these words with hang">>>putDocW 24 ("prefix" <+> hang 4 doc)prefix Indenting these words with hang
This differs from nest, which is based on the current nesting level plus
 i. When you're not sure, try the more efficient nest first. In our
 example, this would yield
>>>let doc = reflow "Indenting these words with nest">>>putDocW 24 ("prefix" <+> nest 4 doc)prefix Indenting these words with nest
hangi doc =align(nesti doc)
Arguments
| :: Doc ann | left delimiter | 
| -> Doc ann | right delimiter | 
| -> Doc ann | separator | 
| -> [Doc ann] | input documents | 
| -> Doc ann | 
( concatenates the documents encloseSep l r sep xs)xs separated by
 sep, and encloses the resulting document by l and r.
The documents are laid out horizontally if that fits the page,
>>>let doc = "list" <+> align (encloseSep lbracket rbracket comma (map pretty [1,20,300,4000]))>>>putDocW 80 doclist [1,20,300,4000]
If there is not enough space, then the input is split into lines entry-wise therwise they are laid out vertically, with separators put in the front:
>>>putDocW 10 doclist [1 ,20 ,300 ,4000]
Note that doc contains an explicit call to align so that the list items
 are aligned vertically.
For putting separators at the end of entries instead, have a look at
 punctuate.
list :: [Doc ann] -> Doc ann Source #
Haskell-inspired variant of encloseSep with braces and comma as
 separator.
>>>let doc = list (map pretty [1,20,300,4000])
>>>putDocW 80 doc[1, 20, 300, 4000]
>>>putDocW 10 doc[ 1 , 20 , 300 , 4000 ]
tupled :: [Doc ann] -> Doc ann Source #
Haskell-inspired variant of encloseSep with parentheses and comma as
 separator.
>>>let doc = tupled (map pretty [1,20,300,4000])
>>>putDocW 80 doc(1, 20, 300, 4000)
>>>putDocW 10 doc( 1 , 20 , 300 , 4000 )
Binary functions
List functions
The sep and cat functions differ in one detail: when grouped, the
 seps replace newlines wich spaces, while the cats simply remove
 them. If you're not sure what you want, start with the seps.
concatWith :: Foldable t => (Doc ann -> Doc ann -> Doc ann) -> t (Doc ann) -> Doc ann Source #
Concatenate all documents element-wise with a binary function.
concatWith_ [] =memptyconcatWith(**) [x,y,z] = x ** y ** z
Multiple convenience definitions based on concatWith are alredy predefined,
 for example
hsep=concatWith(<+>)fillSep=concatWith(\x y -> x<>softline<>y)
This is also useful to define customized joiners,
>>>concatWith (surround dot) ["Data", "Text", "Prettyprint", "Doc"]Data.Text.Prettyprint.Doc
sep family
When grouped, these will replace newlines with spaces.
hsep :: [Doc ann] -> Doc ann Source #
( concatenates all documents hsep xs)xs horizontally with <+>
>>>let docs = Util.words "lorem ipsum dolor sit amet"
>>>hsep docslorem ipsum dolor sit amet
hsep
>>>putDocW 5 (hsep docs)lorem ipsum dolor sit amet
For automatic line breaks, consider using fillSep instead.
vsep :: [Doc ann] -> Doc ann Source #
( concatenates all documents vsep xs)xs above each other. If a
 group undoes the line breaks inserted by vsep, the documents are
 separated with a space instead.
Using vsep alone yields
>>>"prefix" <+> vsep ["text", "to", "lay", "out"]prefix text to lay out
grouping a vsep separates the documents with a space if it fits the
 page (and does nothing otherwise). See the sep
The align function can be used to align the documents under their first
 element:
>>>"prefix" <+> align (vsep ["text", "to", "lay", "out"])prefix text to lay out
Since grouping a vsep is rather common, sep is a built-in for doing
 that.
fillSep :: [Doc ann] -> Doc ann Source #
( concatenates the documents fillSep xs)xs horizontally with <+>linexs. (linegrouped, the documents
 are separated with a space instead of newlines. Use fillCat if you do not
 want a space.)
Let's print some words to fill the line:
>>>let docs = take 20 (cycle ["lorem", "ipsum", "dolor", "sit", "amet"])>>>putDocW 80 ("Docs:" <+> fillSep docs)Docs: lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet
The same document, printed at a width of only 40, yields
>>>putDocW 40 ("Docs:" <+> fillSep docs)Docs: lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet
sep :: [Doc ann] -> Doc ann Source #
( tries laying out the documents sep xs)xs separated with spaces,
 and if this does not fit the page, separates them with newlines. This is what
 differentiates it from vsep, which always lays out its contents beneath
 each other.
>>>let doc = "prefix" <+> sep ["text", "to", "lay", "out"]>>>putDocW 80 docprefix text to lay out
With a narrower layout, the entries are separated by newlines:
>>>putDocW 20 docprefix text to lay out
sep=group.vsep
cat family
When grouped, these will remove newlines.
vcat :: [Doc ann] -> Doc ann Source #
( vertically concatenates the documents vcat xs)xs. If it is
 grouped, the line breaks are removed.
In other words vcatvsepspaces.
>>>let docs = Util.words "lorem ipsum dolor">>>vcat docslorem ipsum dolor>>>group (vcat docs)loremipsumdolor
Since grouping a vcat is rather common, cat is a built-in shortcut for
 it.
fillCat :: [Doc ann] -> Doc ann Source #
( concatenates documents fillCat xs)xs horizontally with <>line'xs. This is similar to how an ordinary word processor
 lays out the text if you just keep typing after you hit the maximum line
 length.
(line'grouped, the documents are separated with nothing
 instead of newlines. See fillSep if you want a space instead.)
Observe the difference between fillSep and fillCat. fillSep
 concatenates the entries spaced when grouped,
>>>let docs = take 20 (cycle (["lorem", "ipsum", "dolor", "sit", "amet"]))>>>putDocW 40 ("Grouped:" <+> group (fillSep docs))Grouped: lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet
On the other hand, fillCat concatenates the entries directly when
 grouped,
>>>putDocW 40 ("Grouped:" <+> group (fillCat docs))Grouped: loremipsumdolorsitametlorem ipsumdolorsitametloremipsumdolorsitamet loremipsumdolorsitamet
cat :: [Doc ann] -> Doc ann Source #
( tries laying out the documents cat xs)xs separated with nothing,
 and if this does not fit the page, separates them with newlines. This is what
 differentiates it from vcat, which always lays out its contents beneath
 each other.
>>>let docs = Util.words "lorem ipsum dolor">>>putDocW 80 ("Docs:" <+> cat docs)Docs: loremipsumdolor
When there is enough space, the documents are put above one another,
>>>putDocW 10 ("Docs:" <+> cat docs)Docs: lorem ipsum dolor
cat=group.vcat
Others
( appends punctuate p xs)p to all but the last document in xs.
>>>let docs = punctuate comma (Util.words "lorem ipsum dolor sit amet")>>>putDocW 80 (hsep docs)lorem, ipsum, dolor, sit, amet
The separators are put at the end of the entries, which we can see if we position the result vertically:
>>>putDocW 20 (vsep docs)lorem, ipsum, dolor, sit, amet
If you want put the commas in front of their elements instead of at the end,
 you should use tupled or, in general, encloseSep.
Reactive/conditional layouts
Lay documents out differently based on current position and the page layout.
column :: (Int -> Doc ann) -> Doc ann Source #
Layout a document depending on which column it starts at. align is
 implemented in terms of column.
>>>column (\l -> "Columns are" <+> pretty l <> "-based.")Columns are 0-based.
>>>let doc = "prefix" <+> column (\l -> "| <- column" <+> pretty l)>>>vsep [indent n doc | n <- [0,4,8]]prefix | <- column 7 prefix | <- column 11 prefix | <- column 15
width :: Doc ann -> (Int -> Doc ann) -> Doc ann Source #
( lays out the document width doc f)doc, and makes the column width
 of it available to a function.
>>>let annotate doc = width (brackets doc) (\w -> " <- width:" <+> pretty w)>>>align (vsep (map annotate ["---", "------", indent 3 "---", vsep ["---", indent 4 "---"]]))[---] <- width: 5 [------] <- width: 8 [ ---] <- width: 8 [--- ---] <- width: 8
pageWidth :: (PageWidth -> Doc ann) -> Doc ann Source #
Layout a document depending on the page width, if one has been specified.
>>>let prettyPageWidth (AvailablePerLine l r) = "Width:" <+> pretty l <> ", ribbon fraction:" <+> pretty r>>>let doc = "prefix" <+> pageWidth (brackets . prettyPageWidth)>>>putDocW 32 (vsep [indent n doc | n <- [0,4,8]])prefix [Width: 32, ribbon fraction: 1.0] prefix [Width: 32, ribbon fraction: 1.0] prefix [Width: 32, ribbon fraction: 1.0]
Filler functions
Fill up available space
( lays out the document fill i x)x. It then appends spaces until
 the width is equal to i. If the width of x is already larger, nothing is
 appended.
This function is quite useful in practice to output a list of bindings:
>>>let types = [("empty","Doc"), ("nest","Int -> Doc -> Doc"), ("fillSep","[Doc] -> Doc")]>>>let ptype (name, tp) = fill 5 (pretty name) <+> "::" <+> pretty tp>>>"let" <+> align (vcat (map ptype types))let empty :: Doc nest :: Int -> Doc -> Doc fillSep :: [Doc] -> Doc
( first lays out the document fillBreak i x)x. It then appends spaces
 until the width is equal to i. If the width of x is already larger than
 i, the nesting level is increased by i and a line is appended. When we
 redefine ptype in the example given in fill to use fillBreak
>>>let types = [("empty","Doc"), ("nest","Int -> Doc -> Doc"), ("fillSep","[Doc] -> Doc")]>>>let ptype (name, tp) = fillBreak 5 (pretty name) <+> "::" <+> pretty tp>>>"let" <+> align (vcat (map ptype types))let empty :: Doc nest :: Int -> Doc -> Doc fillSep :: [Doc] -> Doc
General convenience
Useful helper functions.
( is plural n one many)one if n is 1, and many otherwise. A
 typical use case is  adding a plural "s".
>>>let things = [True]>>>let amount = length things>>>pretty things <+> "has" <+> pretty amount <+> plural "entry" "entries" amount[True] has 1 entry
Bracketing functions
Enclose documents in common ways.
Named characters
Convenience definitions for common characters
Annotations
annotate :: ann -> Doc ann -> Doc ann Source #
Add an annotation to a Doc
This function is only relevant for custom formats with their own annotations, and not relevant for basic prettyprinting. The predefined renderers, e.g. Data.Text.Prettyprint.Doc.Render.Text, should be enough for the most common needs.
unAnnotate :: Doc ann -> Doc xxx Source #
Remove all annotations.
Although unAnnotate is idempotent with respect to rendering,
unAnnotate.unAnnotate=unAnnotate
it should not be used without caution, for each invocation traverses the
 entire contained document. If possible, it is preferrable to unannotate after
 producing the layout by using unAnnotateS.
reAnnotate :: (ann -> ann') -> Doc ann -> Doc ann' Source #
Change the annotation of a Document.
Useful in particular to embed documents with one form of annotation in a more generlly annotated document.
Since this traverses the entire DocreAnnotateS
Since reAnnotate'reAnnotate id = id',
 it is used to define the FunctorDoc
alterAnnotations :: (ann -> [ann']) -> Doc ann -> Doc ann' Source #
Change the annotations of a Document. Individual annotations can be
 removed, changed, or replaced by multiple ones.
This is a general function that combines unAnnotate and reAnnotate, and
 it is useful for mapping semantic annotations (such as »this is a keyword«)
 to display annotations (such as »this is red and underlined«), because some
 backends may not care about certain annotations, while others may.
Annotations earlier in the new list will be applied earlier, i.e. returning
 [Bold, Green] will result in a bold document that contains green text, and
 not vice-versa.
Since this traverses the entire DocalterAnnotationsS
unAnnotateS :: SimpleDocStream ann -> SimpleDocStream xxx Source #
Remove all annotations. unAnnotate for SimpleDocStream.
reAnnotateS :: (ann -> ann') -> SimpleDocStream ann -> SimpleDocStream ann' Source #
Change the annotation of a document. reAnnotate for SimpleDocStream.
alterAnnotationsS :: (ann -> Maybe ann') -> SimpleDocStream ann -> SimpleDocStream ann' Source #
Change the annotation of a document to a different annotation, or none at
 all. alterAnnotations for SimpleDocStream.
Note that the Doc version is more flexible, since it allows changing a
 single annotation to multiple ones.
 (SimpleDocTree restores
 this flexibility again.)
Optimization
fuse :: FusionDepth -> Doc ann -> Doc ann Source #
( combines text nodes so they can be rendered more
 efficiently. A fused document is always laid out identical to its unfused
 version.fuse depth doc)
When laying a Document out to a SimpleDocStream, every component of the
 input is translated directly to the simpler output format. This sometimes
 yields undesirable chunking when many pieces have been concatenated together.
For example
>>>"a" <> "b" <> pretty 'c' <> "d"abcd
results in a chain of four entries in a SimpleDocStream, although this is fully
 equivalent to the tightly packed
>>>"abcd" :: Doc annabcd
which is only a single SimpleDocStream entry, and can be processed faster.
It is therefore a good idea to run fuse on concatenations of lots of small
 strings that are used many times,
>>>let oftenUsed = fuse Shallow ("a" <> "b" <> pretty 'c' <> "d")>>>hsep (replicate 5 oftenUsed)abcd abcd abcd abcd abcd
data FusionDepth Source #
Fusion depth parameter, used by fuse.
Constructors
| Shallow | Do not dive deep into nested documents, fusing mostly concatenations of text nodes together. | 
| Deep | Recurse into all parts of the  This value should only be used if profiling shows it is significantly
 faster than using  | 
Instances
| Eq FusionDepth Source # | |
| Defined in Data.Text.Prettyprint.Doc.Internal | |
| Ord FusionDepth Source # | |
| Defined in Data.Text.Prettyprint.Doc.Internal Methods compare :: FusionDepth -> FusionDepth -> Ordering # (<) :: FusionDepth -> FusionDepth -> Bool # (<=) :: FusionDepth -> FusionDepth -> Bool # (>) :: FusionDepth -> FusionDepth -> Bool # (>=) :: FusionDepth -> FusionDepth -> Bool # max :: FusionDepth -> FusionDepth -> FusionDepth # min :: FusionDepth -> FusionDepth -> FusionDepth # | |
| Show FusionDepth Source # | |
| Defined in Data.Text.Prettyprint.Doc.Internal Methods showsPrec :: Int -> FusionDepth -> ShowS # show :: FusionDepth -> String # showList :: [FusionDepth] -> ShowS # | |
Layout
Laying a Document out produces a straightforward SimpleDocStream
 based on parameters such as page width and ribbon size, by evaluating how
 a Doc fits these constraints the best. There are various ways to render
 a SimpleDocStream. For the common case of rendering a SimpleDocStream
 as plain Text take a look at Data.Text.Prettyprint.Doc.Render.Text.
data SimpleDocStream ann Source #
The data type SimpleDocStream represents laid out documents and is used
 by the display functions.
A simplified view is that Doc = [SimpleDocStream]SimpleDocStreams based on which one fits the
 layout constraints best. This means that SimpleDocStream has all complexity
 contained in Doc resolved, making it very easy to convert it to other
 formats, such as plain text or terminal output.
To write your own DocSimpleDocStream
Constructors
| SFail | |
| SEmpty | |
| SChar Char (SimpleDocStream ann) | |
| SText !Int Text (SimpleDocStream ann) | Some layout algorithms use the Since the frequently used  | 
| SLine !Int (SimpleDocStream ann) | 
 | 
| SAnnPush ann (SimpleDocStream ann) | Add an annotation to the remaining document. | 
| SAnnPop (SimpleDocStream ann) | Remove a previously pushed annotation. | 
Instances
Maximum number of characters that fit in one line. The layout algorithms
 will try not to exceed the set limit by inserting line breaks when applicable
 (e.g. via softline').
Constructors
| AvailablePerLine Int Double | Layouters should not exceed the specified space per line. 
 | 
| Unbounded | Layouters should not introduce line breaks on their own. | 
Instances
| Eq PageWidth Source # | |
| Ord PageWidth Source # | |
| Defined in Data.Text.Prettyprint.Doc.Internal | |
| Show PageWidth Source # | |
newtype LayoutOptions Source #
Options to influence the layout algorithms.
Constructors
| LayoutOptions | |
| Fields | |
Instances
| Eq LayoutOptions Source # | |
| Defined in Data.Text.Prettyprint.Doc.Internal Methods (==) :: LayoutOptions -> LayoutOptions -> Bool # (/=) :: LayoutOptions -> LayoutOptions -> Bool # | |
| Ord LayoutOptions Source # | |
| Defined in Data.Text.Prettyprint.Doc.Internal Methods compare :: LayoutOptions -> LayoutOptions -> Ordering # (<) :: LayoutOptions -> LayoutOptions -> Bool # (<=) :: LayoutOptions -> LayoutOptions -> Bool # (>) :: LayoutOptions -> LayoutOptions -> Bool # (>=) :: LayoutOptions -> LayoutOptions -> Bool # max :: LayoutOptions -> LayoutOptions -> LayoutOptions # min :: LayoutOptions -> LayoutOptions -> LayoutOptions # | |
| Show LayoutOptions Source # | |
| Defined in Data.Text.Prettyprint.Doc.Internal Methods showsPrec :: Int -> LayoutOptions -> ShowS # show :: LayoutOptions -> String # showList :: [LayoutOptions] -> ShowS # | |
defaultLayoutOptions :: LayoutOptions Source #
The default layout options, suitable when you just want some output, and
 don’t particularly care about the details. Used by the Show instance, for
 example.
>>>defaultLayoutOptionsLayoutOptions {layoutPageWidth = AvailablePerLine 80 1.0}
layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann Source #
This is the default layout algorithm, and it is used by show, putDoc
 and hPutDoc.
layoutPrettySimpleDocStream element lookahead when rendering. Consider using the
 smarter, but a bit less performant, layoutSmart
layoutCompact :: Doc ann -> SimpleDocStream ann Source #
(layoutCompact x) lays out the document x without adding any
 indentation. Since no 'pretty' printing is involved, this layouter is very
 fast. The resulting output contains fewer characters than a prettyprinted
 version and can be used for output that is read by other programs.
>>>let doc = hang 4 (vsep ["lorem", "ipsum", hang 4 (vsep ["dolor", "sit"])])>>>doclorem ipsum dolor sit
>>>let putDocCompact = renderIO System.IO.stdout . layoutCompact>>>putDocCompact doclorem ipsum dolor sit
layoutSmart :: LayoutOptions -> Doc ann -> SimpleDocStream ann Source #
A layout algorithm with more lookahead than layoutPretty, that introduces
 line breaks earlier if the content does not (or will not, rather) fit into
 one line.
Considre the following python-ish document,
>>>let fun x = hang 2 ("fun(" <> softline' <> x) <> ")">>>let doc = (fun . fun . fun . fun . fun) (align (list ["abcdef", "ghijklm"]))
which we’ll be rendering using the following pipeline (where the layout algorithm has been left open),
>>>import Data.Text.IO as T>>>import Data.Text.Prettyprint.Doc.Render.Text>>>let hr = pipe <> pretty (replicate (26-2) '-') <> pipe>>>let go layouter x = (T.putStrLn . renderStrict . layouter (LayoutOptions (AvailablePerLine 26 1))) (vsep [hr, x, hr])
If we render this using layoutPrettyfun calls fit into the first line so they will be put
 there,
>>>go layoutPretty doc|------------------------| fun(fun(fun(fun(fun( [ abcdef , ghijklm ]))))) |------------------------|
Note that this exceeds the desired 26 character page width. The same
 document, rendered with layoutSmart
>>>go layoutSmart doc|------------------------| fun( fun( fun( fun( fun( [ abcdef , ghijklm ]))))) |------------------------|
The key difference between layoutPrettylayoutSmart
removeTrailingWhitespace :: SimpleDocStream ann -> SimpleDocStream ann Source #
Remove all trailing space characters.
This has some performance impact, because it does an entire additional pass
 over the SimpleDocStream.
No trimming will be done inside annotations, which are considered to contain
 no (trimmable) whitespace, since the annotation might actually be about the
 whitespace, for example a renderer that colors the background of trailing
 whitespace, as e.g. git diff can be configured to do.
Migration guide
There are 3 main ways to migrate:
- Direct: just replace the previous package and fix the errors
- Using a drop-in replacement mimicing the API of the former module, see
      the prettyprinter-compat-packagepackages
- Using a converter from the old Doctype to the new one, see theprettyprinter-convert-packagepackages
If you're already familiar with (ansi-)wl-pprint, you'll recognize many functions in this module, and they work just the same way. However, a couple of definitions are missing:
- char,- string,- double, … – these are all special cases of the overloaded- pretty
- <$>,- <$$>,- </>,- <//>are special cases of- vsep- vcat- fillSep- fillCat
- If you need Stringoutput, use the backends in the Data.Text.Prettyprint.Doc.Render.String module.
- The display functions are moved to the rendering submodules, for
     example conversion to plain Textis in the Data.Text.Prettyprint.Doc.Render.Text module.
- The render functions are called layout functions.
- SimpleDocwas renamed to- SimpleDocStream- SimpleDocTree.
- Instead of providing an own colorization function for each
     color/intensity/layer combination, they have been combined in color,colorDull,bgColor, andbgColorDullfunctions, which can be found in the ANSI terminal specificprettyprinter-ansi-terminalpackage.