prettyprinter-compat-annotated-wl-pprint-1: Prettyprinter compatibility module for previous users of the annotated-wl-pprint package.

Safe HaskellSafe
LanguageHaskell2010

Text.PrettyPrint.Annotated.Leijen

Description

Deprecated: Compatibility module for users of annotated-wl-pprint - use Data.Text.Prettyprint.Doc instead

Synopsis

Documentation

data Doc ann :: * -> * #

The abstract data type Doc ann represents pretty documents that have been annotated with data of type ann.

More specifically, a value of type Doc represents a non-empty set of possible layouts of a document. The layout functions select one of these possibilities, taking into account things like the width of the output document.

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

Functor Doc

Alter the document’s annotations.

This instance makes Doc more flexible (because it can be used in Functor-polymorphic values), but fmap is much less readable compared to using reAnnotate in code that only works for Doc anyway. Consider using the latter when the type does not matter.

Methods

fmap :: (a -> b) -> Doc a -> Doc b #

(<$) :: a -> Doc b -> Doc a #

Show (Doc ann)

(show doc) prettyprints document doc with defaultLayoutOptions, ignoring all annotations.

Methods

showsPrec :: Int -> Doc ann -> ShowS #

show :: Doc ann -> String #

showList :: [Doc ann] -> ShowS #

IsString (Doc ann)
>>> pretty ("hello\nworld")
hello
world

This instance uses the Pretty Text instance, and uses the same newline to line conversion.

Methods

fromString :: String -> Doc ann #

Generic (Doc ann) 

Associated Types

type Rep (Doc ann) :: * -> * #

Methods

from :: Doc ann -> Rep (Doc ann) x #

to :: Rep (Doc ann) x -> Doc ann #

Semigroup (Doc ann)
x <> y = hcat [x, y]
>>> "hello" <> "world" :: Doc ann
helloworld

Methods

(<>) :: Doc ann -> Doc ann -> Doc ann #

sconcat :: NonEmpty (Doc ann) -> Doc ann #

stimes :: Integral b => b -> Doc ann -> Doc ann #

Monoid (Doc ann)
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld

Methods

mempty :: Doc ann #

mappend :: Doc ann -> Doc ann -> Doc ann #

mconcat :: [Doc ann] -> Doc ann #

Pretty (Doc ann)

Does not change the text, but removes all annotations. Pitfall: since this un-annotates its argument, nesting it means multiple, potentially costly, traversals over the Doc.

>>> pretty 123
123
>>> pretty (pretty 123)
123

Methods

pretty :: Doc ann -> Doc ann #

prettyList :: [Doc ann] -> Doc ann #

type Rep (Doc ann) 
type Rep (Doc ann) = D1 (MetaData "Doc" "Data.Text.Prettyprint.Doc.Internal" "prettyprinter-1-D6eInObgHI9BRj8OCwibwl" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Fail" PrefixI False) U1) ((:+:) (C1 (MetaCons "Empty" PrefixI False) U1) (C1 (MetaCons "Char" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char))))) ((:+:) (C1 (MetaCons "Text" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:+:) (C1 (MetaCons "Line" PrefixI False) U1) (C1 (MetaCons "FlatAlt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)))))))) ((:+:) ((:+:) (C1 (MetaCons "Cat" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))))) ((:+:) (C1 (MetaCons "Nest" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))))) (C1 (MetaCons "Union" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))))))) ((:+:) ((:+:) (C1 (MetaCons "Column" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> Doc ann)))) (C1 (MetaCons "WithPageWidth" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PageWidth -> Doc ann))))) ((:+:) (C1 (MetaCons "Nesting" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> Doc ann)))) (C1 (MetaCons "Annotated" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ann)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)))))))))

type SpanList a = [(Int, Int, a)] Source #

putDoc :: Doc () -> IO () Source #

hPutDoc :: Handle -> Doc () -> IO () Source #

empty :: Doc ann Source #

char :: Char -> Doc ann Source #

text :: String -> Doc ann Source #

(<>) :: Semigroup a => a -> a -> a #

An associative operation.

(a <> b) <> c = a <> (b <> c)

If a is also a Monoid we further require

(<>) = mappend

nest #

Arguments

:: Int

Change of nesting level

-> Doc ann 
-> Doc ann 

(nest i x) lays out the document x with the current indentation level increased by i. Negative values are allowed, and decrease the nesting level accordingly.

>>> vsep [nest 4 (vsep ["lorem", "ipsum", "dolor"]), "sit", "amet"]
lorem
    ipsum
    dolor
sit
amet

See also hang, align and indent.

line :: Doc ann #

The line document advances to the next line and indents to the current nesting level.

>>> let doc = "lorem ipsum" <> line <> "dolor sit amet"
>>> doc
lorem ipsum
dolor sit amet

line behaves like space if the line break is undone by group:

>>> group doc
lorem ipsum dolor sit amet

group :: Doc ann -> Doc ann #

(group x) tries laying out 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.

softline :: Doc ann #

softline behaves like space if the resulting output fits the page, otherwise like line.

Here, we have enough space to put everything in one line:

>>> let doc = "lorem ipsum" <> softline <> "dolor sit amet"
>>> putDocW 80 doc
lorem ipsum dolor sit amet

If we narrow the page to width 10, the layouter produces a line break:

>>> putDocW 10 doc
lorem ipsum
dolor sit amet
softline = group line

align :: Doc ann -> Doc ann #

(align x) lays out the document 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's contents all start in the same column,

>>> "lorem" <+> align (vsep ["ipsum", "dolor"])
lorem ipsum
      dolor

hang #

Arguments

:: Int

Change of nesting level, relative to the start of the first line

-> Doc ann 
-> Doc ann 

(hang i x) lays out the document 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
hang i doc = align (nest i doc)

indent #

Arguments

:: Int

Number of spaces to increase indentation by

-> Doc ann 
-> Doc ann 

(indent i x) indents document x with i spaces, starting from the current cursor position.

>>> let doc = reflow "The indent function indents these words!"
>>> putDocW 24 ("prefix" <> indent 4 doc)
prefix    The indent
          function
          indents these
          words!
indent i d = hang i ({i spaces} <> d)

encloseSep #

Arguments

:: Doc ann

left delimiter

-> Doc ann

right delimiter

-> Doc ann

separator

-> [Doc ann]

input documents

-> Doc ann 

(encloseSep l r sep xs) concatenates the documents 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" <+> encloseSep lbracket rbracket comma (map pretty [1,20,300,4000])
>>> putDocW 80 doc
list [1,20,300,4000]

If there is not enough space, then the input is split into lines entry-wise therwise they are aligned vertically, with separators put in the front:

>>> putDocW 10 doc
list [1
     ,20
     ,300
     ,4000]

For putting separators at the end of entries instead, have a look at punctuate.

list :: [Doc ann] -> Doc ann #

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 #

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 )

semiBraces :: [Doc ann] -> Doc ann Source #

(<+>) :: Doc ann -> Doc ann -> Doc ann #

(x <+> y) concatenates document x and y with a space in between.

>>> "hello" <+> "world"
hello world
x <+> y = x <> space <> y

(<$>) :: Doc ann -> Doc ann -> Doc ann Source #

(</>) :: Doc ann -> Doc ann -> Doc ann Source #

(<$$>) :: Doc ann -> Doc ann -> Doc ann Source #

(<//>) :: Doc ann -> Doc ann -> Doc ann Source #

hsep :: [Doc ann] -> Doc ann #

(hsep xs) concatenates all documents xs horizontally with <+>, i.e. it puts a space between all entries.

>>> let docs = Util.words "lorem ipsum dolor sit amet"
>>> hsep docs
lorem ipsum dolor sit amet

hsep does not introduce line breaks on its own, even when the page is too narrow:

>>> putDocW 5 (hsep docs)
lorem ipsum dolor sit amet

For automatic line breaks, consider using fillSep instead.

vsep :: [Doc ann] -> Doc ann #

(vsep xs) concatenates all documents 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 convenience function for this use case.

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 #

(fillSep xs) concatenates the documents xs horizontally with <+> as long as it fits the page, then inserts a line and continues doing that for all documents in xs. (line means that if grouped, 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 #

(sep xs) tries laying out the documents 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 doc
prefix text to lay out

With a narrower layout, the entries are separated by newlines:

>>> putDocW 20 doc
prefix text
to
lay
out
sep = group . vsep

hcat :: [Doc ann] -> Doc ann #

(hcat xs) concatenates all documents xs horizontally with <> (i.e. without any spacing).

It is provided only for consistency, since it is identical to mconcat.

>>> let docs = Util.words "lorem ipsum dolor"
>>> hcat docs
loremipsumdolor

vcat :: [Doc ann] -> Doc ann #

(vcat xs) vertically concatenates the documents xs. If it is grouped, the line breaks are removed.

In other words vcat is like vsep, with newlines removed instead of replaced by spaces.

>>> let docs = Util.words "lorem ipsum dolor"
>>> vcat docs
lorem
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 #

(fillCat xs) concatenates documents xs horizontally with <> as long as it fits the page, then inserts a line' and continues doing that for all documents in 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' means that if 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 #

(cat xs) tries laying out the documents 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

punctuate #

Arguments

:: Doc ann

Punctuation, e.g. comma

-> [Doc ann] 
-> [Doc ann] 

(punctuate p xs) appends 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.

fill #

Arguments

:: Int

Append spaces until the document is at least this wide

-> Doc ann 
-> Doc ann 

(fill i x) lays out the document 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

fillBreak #

Arguments

:: Int

Append spaces until the document is at least this wide

-> Doc ann 
-> Doc ann 

(fillBreak i x) first lays out the document 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, we get a useful variation of the output:

>>> 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

enclose #

Arguments

:: Doc ann

L

-> Doc ann

R

-> Doc ann

x

-> Doc ann

LxR

(enclose l r x) encloses document x between documents l and r using <>.

>>> enclose "A" "Z" "·"
A·Z
enclose l r x = l <> x <> r

squotes :: Doc ann -> Doc ann #

>>> squotes "·"
'·'

dquotes :: Doc ann -> Doc ann #

>>> dquotes "·"
"·"

parens :: Doc ann -> Doc ann #

>>> parens "·"
(·)

angles :: Doc ann -> Doc ann #

>>> angles "·"
<·>

braces :: Doc ann -> Doc ann #

>>> braces "·"
{·}

brackets :: Doc ann -> Doc ann #

>>> brackets "·"
[·]

lparen :: Doc ann #

>>> lparen
(

rparen :: Doc ann #

>>> rparen
)

langle :: Doc ann #

>>> langle
<

rangle :: Doc ann #

>>> rangle
>

lbrace :: Doc ann #

>>> lbrace
{

rbrace :: Doc ann #

>>> rbrace
}

lbracket :: Doc ann #

>>> lbracket
[

rbracket :: Doc ann #

>>> rbracket
]

squote :: Doc ann #

>>> squote
'

dquote :: Doc ann #

>>> dquote
"

semi :: Doc ann #

>>> semi
;

colon :: Doc ann #

>>> colon
:

comma :: Doc ann #

>>> comma
,

space :: Doc ann #

>>> "a" <> space <> "b"
a b

This is mostly used via <+>,

>>> "a" <+> "b"
a b

dot :: Doc ann #

>>> dot
.

backslash :: Doc ann #

>>> backslash
\

equals :: Doc ann #

>>> equals
=

pipe :: Doc ann #

>>> pipe
|

int :: Int -> Doc ann Source #

float :: Float -> Doc ann Source #

bool :: Bool -> Doc ann Source #

annotate :: ann -> Doc ann -> Doc ann #

Add an annotation to a Doc. This annotation can then be used by the renderer to e.g. add color to certain parts of the output. For a full tutorial example on how to use it, see the Data.Text.Prettyprint.Doc.Render.Tutorials.StackMachineTutorial or Data.Text.Prettyprint.Doc.Render.Tutorials.TreeRenderingTutorial modules.

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.

noAnnotate :: Doc ann -> Doc xxx Source #

renderPretty :: Float -> Int -> Doc ann -> SimpleDoc ann Source #

displayDecoratedA :: (Applicative f, Monoid b) => (String -> f b) -> (a -> f b) -> (a -> f b) -> SimpleDoc a -> f b Source #

column :: (Int -> Doc ann) -> Doc ann #

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

nesting :: (Int -> Doc ann) -> Doc ann #

Layout a document depending on the current nesting level. align is implemented in terms of nesting.

>>> let doc = "prefix" <+> nesting (\l -> brackets ("Nested:" <+> pretty l))
>>> vsep [indent n doc | n <- [0,4,8]]
prefix [Nested: 0]
    prefix [Nested: 4]
        prefix [Nested: 8]

width :: Doc ann -> (Int -> Doc ann) -> Doc ann #

(width doc f) lays out the document 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