| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Options.Applicative.Help.Pretty
Synopsis
- (<>) :: Semigroup a => a -> a -> a
 - pipe :: Doc ann
 - equals :: Doc ann
 - backslash :: Doc ann
 - slash :: Doc ann
 - dot :: Doc ann
 - space :: Doc ann
 - comma :: Doc ann
 - colon :: Doc ann
 - semi :: Doc ann
 - rbrace :: Doc ann
 - lbrace :: Doc ann
 - rbracket :: Doc ann
 - lbracket :: Doc ann
 - rangle :: Doc ann
 - langle :: Doc ann
 - rparen :: Doc ann
 - lparen :: Doc ann
 - dquote :: Doc ann
 - squote :: Doc ann
 - braces :: Doc ann -> Doc ann
 - brackets :: Doc ann -> Doc ann
 - angles :: Doc ann -> Doc ann
 - parens :: Doc ann -> Doc ann
 - dquotes :: Doc ann -> Doc ann
 - squotes :: Doc ann -> Doc ann
 - layoutCompact :: Doc ann1 -> SimpleDocStream ann2
 - layoutSmart :: LayoutOptions -> Doc ann -> SimpleDocStream ann
 - layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann
 - defaultLayoutOptions :: LayoutOptions
 - removeTrailingWhitespace :: SimpleDocStream ann -> SimpleDocStream ann
 - fuse :: FusionDepth -> Doc ann -> Doc ann
 - alterAnnotationsS :: (ann -> Maybe ann') -> SimpleDocStream ann -> SimpleDocStream ann'
 - reAnnotateS :: (ann -> ann') -> SimpleDocStream ann -> SimpleDocStream ann'
 - unAnnotateS :: SimpleDocStream ann -> SimpleDocStream xxx
 - alterAnnotations :: (ann -> [ann']) -> Doc ann -> Doc ann'
 - reAnnotate :: (ann -> ann') -> Doc ann -> Doc ann'
 - unAnnotate :: Doc ann -> Doc xxx
 - annotate :: ann -> Doc ann -> Doc ann
 - surround :: Doc ann -> Doc ann -> Doc ann -> Doc ann
 - enclose :: Doc ann -> Doc ann -> Doc ann -> Doc ann
 - plural :: (Num amount, Eq amount) => doc -> doc -> amount -> doc
 - fillBreak :: Int -> Doc ann -> Doc ann
 - fill :: Int -> Doc ann -> Doc ann
 - pageWidth :: (PageWidth -> Doc ann) -> Doc ann
 - width :: Doc ann -> (Int -> Doc ann) -> Doc ann
 - nesting :: (Int -> Doc ann) -> Doc ann
 - column :: (Int -> Doc ann) -> Doc ann
 - punctuate :: Doc ann -> [Doc ann] -> [Doc ann]
 - cat :: [Doc ann] -> Doc ann
 - fillCat :: [Doc ann] -> Doc ann
 - vcat :: [Doc ann] -> Doc ann
 - hcat :: [Doc ann] -> Doc ann
 - sep :: [Doc ann] -> Doc ann
 - fillSep :: [Doc ann] -> Doc ann
 - vsep :: [Doc ann] -> Doc ann
 - hsep :: [Doc ann] -> Doc ann
 - concatWith :: Foldable t => (Doc ann -> Doc ann -> Doc ann) -> t (Doc ann) -> Doc ann
 - (<+>) :: Doc ann -> Doc ann -> Doc ann
 - tupled :: [Doc ann] -> Doc ann
 - list :: [Doc ann] -> Doc ann
 - encloseSep :: Doc ann -> Doc ann -> Doc ann -> [Doc ann] -> Doc ann
 - indent :: Int -> Doc ann -> Doc ann
 - hang :: Int -> Doc ann -> Doc ann
 - align :: Doc ann -> Doc ann
 - flatAlt :: Doc ann -> Doc ann -> Doc ann
 - group :: Doc ann -> Doc ann
 - hardline :: Doc ann
 - softline' :: Doc ann
 - softline :: Doc ann
 - line' :: Doc ann
 - line :: Doc ann
 - nest :: Int -> Doc ann -> Doc ann
 - emptyDoc :: Doc ann
 - unsafeViaShow :: Show a => a -> Doc ann
 - viaShow :: Show a => a -> Doc ann
 - class Pretty a where
- pretty :: a -> Doc ann
 - prettyList :: [a] -> 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 {}
 - module Prettyprinter.Render.Terminal
 - type Doc = Doc AnsiStyle
 - type SimpleDoc = SimpleDocStream AnsiStyle
 - (.$.) :: Doc -> Doc -> Doc
 - (</>) :: Doc -> Doc -> Doc
 - groupOrNestLine :: Doc -> Doc
 - altSep :: Doc -> Doc -> Doc
 - hangAtIfOver :: Int -> Int -> Doc -> Doc
 - prettyString :: Double -> Int -> Doc -> String
 
Documentation
(<>) :: Semigroup a => a -> a -> a infixr 6 #
An associative operation.
>>>[1,2,3] <> [4,5,6][1,2,3,4,5,6]
layoutCompact :: Doc ann1 -> SimpleDocStream ann2 #
(layoutCompact x) lays out the document x without adding any
 indentation and without preserving annotations.
 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 #
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.
Consider 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 Prettyprinter.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 layoutPretty with a page width of 26 characters
 per line, all the fun 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 , fits the layout contstraints:layoutSmart
>>>go layoutSmart doc|------------------------| fun( fun( fun( fun( fun( [ abcdef , ghijklm ]))))) |------------------------|
The key difference between layoutPretty and layoutSmart is that the
 latter will check the potential document until it encounters a line with the
 same indentation or less than the start of the document. Any line encountered
 earlier is assumed to belong to the same syntactic structure.
 layoutPretty checks only the first line.
Consider for example the question of whether the As fit into the document
 below:
1 A 2 A 3 A 4 B 5 B
layoutPretty will check only line 1, ignoring whether e.g. line 2 might
 already be too wide.
 By contrast, layoutSmart stops only once it reaches line 4, where the B
 has the same indentation as the first A.
layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann #
This is the default layout algorithm, and it is used by show, putDoc
 and hPutDoc.
 commits to rendering something in a certain way if the next
 element fits the layout constraints; in other words, it has one
 layoutPrettySimpleDocStream element lookahead when rendering. Consider using the
 smarter, but a bit less performant,  algorithm if the results
 seem to run off to the right before having lots of line breaks.layoutSmart
defaultLayoutOptions :: LayoutOptions #
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}
removeTrailingWhitespace :: SimpleDocStream ann -> SimpleDocStream ann #
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.
Historical note: Since v1.7.0, layoutPretty and layoutSmart avoid
 producing the trailing whitespace that was the original motivation for
 creating removeTrailingWhitespace.
 See https://github.com/quchen/prettyprinter/pull/139 for some background
 info.
fuse :: FusionDepth -> Doc ann -> Doc ann #
( 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
alterAnnotationsS :: (ann -> Maybe ann') -> SimpleDocStream ann -> SimpleDocStream ann' #
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.)
reAnnotateS :: (ann -> ann') -> SimpleDocStream ann -> SimpleDocStream ann' #
Change the annotation of a document. reAnnotate for SimpleDocStream.
unAnnotateS :: SimpleDocStream ann -> SimpleDocStream xxx #
Remove all annotations. unAnnotate for SimpleDocStream.
alterAnnotations :: (ann -> [ann']) -> Doc ann -> Doc ann' #
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  tree, including parts that are not
 rendered due to other layouts fitting better, it is preferrable to reannotate
 after producing the layout by using Doc.alterAnnotationsS
reAnnotate :: (ann -> ann') -> Doc ann -> Doc ann' #
Change the annotation of a Document.
Useful in particular to embed documents with one form of annotation in a more generally annotated document.
Since this traverses the entire  tree, including parts that are not
 rendered due to other layouts fitting better, it is preferrable to reannotate
 after producing the layout by using Doc.reAnnotateS
Since  has the right type and satisfies reAnnotate'reAnnotate id = id',
 it is used to define the  instance of Functor.Doc
unAnnotate :: Doc ann -> Doc xxx #
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.
annotate :: ann -> Doc ann -> Doc ann #
Add an annotation to a . 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
 Prettyprinter.Render.Tutorials.StackMachineTutorial or
 Prettyprinter.Render.Tutorials.TreeRenderingTutorial modules.Doc
This function is only relevant for custom formats with their own annotations, and not relevant for basic prettyprinting. The predefined renderers, e.g. Prettyprinter.Render.Text, should be enough for the most common needs.
( 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
( 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 , we get
 a useful variation of the output: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
( 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
pageWidth :: (PageWidth -> Doc ann) -> Doc ann #
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]
width :: Doc ann -> (Int -> Doc ann) -> Doc ann #
( 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
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
( 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.
( 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
fillCat :: [Doc ann] -> Doc ann #
( concatenates documents fillCat xs)xs horizontally with  as
 long as it fits the page, then inserts a <> and continues doing that
 for all documents in 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.
( means that if 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
vcat :: [Doc ann] -> Doc ann #
( vertically concatenates the documents vcat xs)xs. If it is
 grouped, the line breaks are removed.
In other words  is like vcat, with newlines removed instead of
 replaced by vsepspaces.
>>>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.
( 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
fillSep :: [Doc ann] -> Doc ann #
( concatenates the documents fillSep xs)xs horizontally with 
 as long as it fits the page, then inserts a <+> and continues doing that
 for all documents in linexs. ( means that if 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
vsep :: [Doc ann] -> Doc ann #
( 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  convenience function for
 this use case.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.
hsep :: [Doc ann] -> Doc ann #
( concatenates all documents hsep xs)xs horizontally with ,
 i.e. it puts a space between all entries.<+>
>>>let docs = Util.words "lorem ipsum dolor sit amet"
>>>hsep docslorem ipsum dolor sit amet
 does not introduce line breaks on its own, even when the page is too
 narrow:hsep
>>>putDocW 5 (hsep docs)lorem ipsum dolor sit amet
For automatic line breaks, consider using fillSep instead.
concatWith :: Foldable t => (Doc ann -> Doc ann -> Doc ann) -> t (Doc ann) -> Doc ann #
Concatenate all documents element-wise with a binary function.
concatWith_ [] =memptyconcatWith(**) [x,y,z] = x ** y ** z
Multiple convenience definitions based on concatWith are already predefined,
 for example:
hsep=concatWith(<+>)fillSep=concatWith(\x y -> x<>softline<>y)
This is also useful to define customized joiners:
>>>concatWith (surround dot) ["Prettyprinter", "Render", "Text"]Prettyprinter.Render.Text
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 )
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 ]
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.
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)
( 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 's contents all start in the
 same column:vsep
>>>"lorem" <+> align (vsep ["ipsum", "dolor"])lorem ipsum dolor
By default, ( renders as flatAlt x y)x. However when grouped,
 y will be preferred, with x as the fallback for the case when y
 doesn't fit.
>>>let doc = flatAlt "a" "b">>>putDoc doca>>>putDoc (group doc)b>>>putDocW 0 (group doc)a
flatAlt is particularly useful for defining conditional separators such as
softline =group(flatAlthardline" ")
>>>let hello = "Hello" <> softline <> "world!">>>putDocW 12 helloHello world!>>>putDocW 11 helloHello world!
Example: Haskell's do-notation
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
Notes
Users should be careful to choose x to be less wide than y.
 Otherwise, if y turns out not to fit the page, we fall back on an even
 wider layout:
>>>let ugly = group (flatAlt "even wider" "too wide")>>>putDocW 7 uglyeven wider
Also note that group will flatten y:
>>>putDoc (group (flatAlt "x" ("y" <> line <> "y")))y y
This also means that an "unflattenable" y which contains a hard linebreak
 will never be rendered:
>>>putDoc (group (flatAlt "x" ("y" <> hardline <> "y")))x
( tries laying out group x)x into a single line by removing the
 contained line breaks; if this does not fit the page, or when a hardline
 within x prevents it from being flattened, 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.
A  is always laid out as a line break, even when 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
 is like softline', but behaves like softline if the
 resulting output does not fit on the page (instead of mempty). In other
 words, space is to line how line' is to softline.softline'
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'
softline behaves like  if the resulting output fits the page,
 otherwise like space.line
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
( lays out the document nest i x)x with the current nesting level
 (indentation of the following lines) 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
unsafeViaShow :: Show a => a -> Doc ann #
viaShow :: Show a => a -> Doc ann #
Convenience function to convert a Showable value to a Doc. If the
 String does not contain newlines, consider using the more performant
 unsafeViaShow.
Minimal complete definition
Methods
>>>pretty 1 <+> pretty "hello" <+> pretty 1.2341 hello 1.234
prettyList :: [a] -> Doc ann #
 is only used to define the prettyListinstance
 . 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  | |
data FusionDepth #
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
| Show FusionDepth | |
Defined in Prettyprinter.Internal Methods showsPrec :: Int -> FusionDepth -> ShowS # show :: FusionDepth -> String # showList :: [FusionDepth] -> ShowS #  | |
| Eq FusionDepth | |
Defined in Prettyprinter.Internal  | |
| Ord FusionDepth | |
Defined in Prettyprinter.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 #  | |
data SimpleDocStream ann #
The data type SimpleDocStream represents laid out documents and is used
 by the display functions.
A simplified view is that , and the layout
 functions pick one of the 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  to X converter, it is therefore sufficient to
 convert from Doc. The »Render« submodules provide some
 built-in converters to do so, and helpers to create own ones.SimpleDocStream
Constructors
| SFail | |
| SEmpty | |
| SChar !Char (SimpleDocStream ann) | |
| SText !Int !Text (SimpleDocStream ann) | |
| 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
| Show PageWidth | |
| Eq PageWidth | |
| Ord PageWidth | |
newtype LayoutOptions #
Options to influence the layout algorithms.
Constructors
| LayoutOptions | |
Fields  | |
Instances
| Show LayoutOptions | |
Defined in Prettyprinter.Internal Methods showsPrec :: Int -> LayoutOptions -> ShowS # show :: LayoutOptions -> String # showList :: [LayoutOptions] -> ShowS #  | |
| Eq LayoutOptions | |
Defined in Prettyprinter.Internal Methods (==) :: LayoutOptions -> LayoutOptions -> Bool # (/=) :: LayoutOptions -> LayoutOptions -> Bool #  | |
| Ord LayoutOptions | |
Defined in Prettyprinter.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 #  | |
type SimpleDoc = SimpleDocStream AnsiStyle Source #
groupOrNestLine :: Doc -> Doc Source #
Render flattened text on this line, or start a new line before rendering any text.
This will also nest subsequent lines in the group.
altSep :: Doc -> Doc -> Doc Source #
Separate items in an alternative with a pipe.
If the first document and the pipe don't fit on the line, then mandatorily flow the next entry onto the following line.
The (//) softbreak ensures that if the document does fit on the line, there is at least a space, but it's possible for y to still appear on the next line.
hangAtIfOver :: Int -> Int -> Doc -> Doc Source #
Printer hacks to get nice indentation for long commands and subcommands.
If we're starting this section over the desired width (usually 1/3 of the ribbon), then we will make a line break, indent all of the usage, and go.
The ifAtRoot is an interesting clause. If this whole
   operation is put under a group then the linebreak
   will disappear; then item d will therefore not be at
   the starting column, and it won't be indented more.