prettyprinter-1.3.0: A modern, easy to use, well-documented, extensible pretty-printer.

Safe HaskellSafe
LanguageHaskell2010

Data.Text.Prettyprint.Doc.Internal

Description

Warning: internal module! This means that the API may change arbitrarily between versions without notice. Depending on this module may lead to unexpected breakages, so proceed with caution!

For a stable API, use the non-internal modules. For the special case of writing adaptors to this library’s Doc type, see Data.Text.Prettyprint.Doc.Internal.Type.

Synopsis

Documentation

data PageWidth Source #

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.

  • The Int is the number of characters, including whitespace, that fit in a line. A typical value is 80.
  • The Double is the ribbon with, i.e. the fraction of the total page width that can be printed on. This allows limiting the length of printable text per line. Values must be between 0 and 1, and 0.4 to 1 is typical.
Unbounded

Layouters should not introduce line breaks on their own.

data LayoutPipeline ann Source #

List of nesting level/document pairs yet to be laid out.

Constructors

Nil 
Cons !Int (Doc ann) (LayoutPipeline ann) 
UndoAnn (LayoutPipeline ann) 

newtype FittingPredicate ann Source #

Decide whether a SimpleDocStream fits the constraints given, namely

  • page width
  • minimum nesting level to fit in
  • width in which to fit the first line; Nothing is unbounded

Constructors

FittingPredicate (PageWidth -> Int -> Maybe Int -> SimpleDocStream ann -> Bool) 

data WhitespaceStrippingState Source #

Constructors

WssAnnotationLevel !Int 
WssWithheldWhitespace [Int] !Int
Newline with indentation i
Spaces

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], and the layout functions pick one of the 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 Doc to X converter, it is therefore sufficient to convert from SimpleDocStream. The »Render« submodules provide some built-in converters to do so, and helpers to create own ones.

Constructors

SFail 
SEmpty 
SChar Char (SimpleDocStream ann) 
SText !Int Text (SimpleDocStream ann)

Some layout algorithms use the Since the frequently used length of the Doc, which scales linearly with its length, we cache it in this constructor.

SLine !Int (SimpleDocStream ann)

Int = indentation level for the (next) line

SAnnPush ann (SimpleDocStream ann)

Add an annotation to the remaining document.

SAnnPop (SimpleDocStream ann)

Remove a previously pushed annotation.

Instances
Functor SimpleDocStream Source #

Alter the document’s annotations.

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

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

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

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

Foldable SimpleDocStream Source #

Collect all annotations from a document.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

fold :: Monoid m => SimpleDocStream m -> m #

foldMap :: Monoid m => (a -> m) -> SimpleDocStream a -> m #

foldr :: (a -> b -> b) -> b -> SimpleDocStream a -> b #

foldr' :: (a -> b -> b) -> b -> SimpleDocStream a -> b #

foldl :: (b -> a -> b) -> b -> SimpleDocStream a -> b #

foldl' :: (b -> a -> b) -> b -> SimpleDocStream a -> b #

foldr1 :: (a -> a -> a) -> SimpleDocStream a -> a #

foldl1 :: (a -> a -> a) -> SimpleDocStream a -> a #

toList :: SimpleDocStream a -> [a] #

null :: SimpleDocStream a -> Bool #

length :: SimpleDocStream a -> Int #

elem :: Eq a => a -> SimpleDocStream a -> Bool #

maximum :: Ord a => SimpleDocStream a -> a #

minimum :: Ord a => SimpleDocStream a -> a #

sum :: Num a => SimpleDocStream a -> a #

product :: Num a => SimpleDocStream a -> a #

Traversable SimpleDocStream Source #

Transform a document based on its annotations, possibly leveraging Applicative effects.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

traverse :: Applicative f => (a -> f b) -> SimpleDocStream a -> f (SimpleDocStream b) #

sequenceA :: Applicative f => SimpleDocStream (f a) -> f (SimpleDocStream a) #

mapM :: Monad m => (a -> m b) -> SimpleDocStream a -> m (SimpleDocStream b) #

sequence :: Monad m => SimpleDocStream (m a) -> m (SimpleDocStream a) #

Eq ann => Eq (SimpleDocStream ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Ord ann => Ord (SimpleDocStream ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Show ann => Show (SimpleDocStream ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Generic (SimpleDocStream ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Associated Types

type Rep (SimpleDocStream ann) :: Type -> Type #

Methods

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

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

type Rep (SimpleDocStream ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

type Rep (SimpleDocStream ann) = D1 (MetaData "SimpleDocStream" "Data.Text.Prettyprint.Doc.Internal" "prettyprinter-1.3.0-6qg3eRt5h66FauUzehlm4q" False) ((C1 (MetaCons "SFail" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SEmpty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SChar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDocStream ann))))) :+: ((C1 (MetaCons "SText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDocStream ann)))) :+: C1 (MetaCons "SLine" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDocStream ann)))) :+: (C1 (MetaCons "SAnnPush" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ann) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDocStream ann))) :+: C1 (MetaCons "SAnnPop" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDocStream ann))))))

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 Doc, including different layout alternatives, and location-sensitive values such as created by nesting which cannot be fused before, but only during, the layout process. As a result, the performance cost of using deep fusion is often hard to predict, and depends on the interplay between page layout and document to prettyprint.

This value should only be used if profiling shows it is significantly faster than using Shallow.

class Pretty a where Source #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann Source #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

pretty :: Show a => a -> Doc ann Source #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

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

prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]
Instances
Pretty Bool Source #
>>> pretty True
True
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Bool -> Doc ann Source #

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

Pretty Char Source #

Instead of (pretty '\n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Char -> Doc ann Source #

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

Pretty Double Source #
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Double -> Doc ann Source #

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

Pretty Float Source #
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Float -> Doc ann Source #

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

Pretty Int Source #
>>> pretty (123 :: Int)
123
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int -> Doc ann Source #

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

Pretty Int8 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int8 -> Doc ann Source #

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

Pretty Int16 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int16 -> Doc ann Source #

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

Pretty Int32 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int32 -> Doc ann Source #

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

Pretty Int64 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int64 -> Doc ann Source #

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

Pretty Integer Source #
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Integer -> Doc ann Source #

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

Pretty Natural Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Natural -> Doc ann Source #

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

Pretty Word Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word -> Doc ann Source #

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

Pretty Word8 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word8 -> Doc ann Source #

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

Pretty Word16 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word16 -> Doc ann Source #

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

Pretty Word32 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word32 -> Doc ann Source #

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

Pretty Word64 Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word64 -> Doc ann Source #

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

Pretty () Source #
>>> pretty ()
()

The argument is not used,

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: () -> Doc ann Source #

prettyList :: [()] -> Doc ann Source #

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 ([] :: [Void])
[]
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Void -> Doc ann Source #

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

Pretty Text Source #

(lazy Doc instance, identical to the strict version)

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Text -> Doc ann Source #

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

Pretty Text Source #

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Text -> Doc ann Source #

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

Pretty a => Pretty [a] Source #
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: [a] -> Doc ann Source #

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

Pretty a => Pretty (Maybe a) Source #

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Maybe a -> Doc ann Source #

prettyList :: [Maybe a] -> Doc ann Source #

Pretty a => Pretty (Identity a) Source #
>>> pretty (Identity 1)
1
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Identity a -> Doc ann Source #

prettyList :: [Identity a] -> Doc ann Source #

Pretty a => Pretty (NonEmpty a) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: NonEmpty a -> Doc ann Source #

prettyList :: [NonEmpty a] -> Doc ann Source #

(Pretty a1, Pretty a2) => Pretty (a1, a2) Source #
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: (a1, a2) -> Doc ann Source #

prettyList :: [(a1, a2)] -> Doc ann Source #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) Source #
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann Source #

prettyList :: [(a1, a2, a3)] -> Doc ann Source #

Pretty a => Pretty (Const a b) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Const a b -> Doc ann Source #

prettyList :: [Const a b] -> Doc ann Source #

data Doc ann Source #

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

Constructors

Fail

Occurs when flattening a line. The layouter will reject this document, choosing a more suitable rendering.

Empty

The empty document; conceptually the unit of Cat

Char !Char

invariant: not '\n'

Text !Int !Text

Invariants: at least two characters long, does not contain '\n'. For empty documents, there is Empty; for singleton documents, there is Char; newlines should be replaced by e.g. Line.

Since the frequently used length of Doc is O(length), we cache it in this constructor.

Line

Hard line break

FlatAlt (Doc ann) (Doc ann)

Lay out the first Doc, but when flattened (via group), fall back to the second. The flattened version should in general be higher and narrower than the fallback.

Cat (Doc ann) (Doc ann)

Concatenation of two documents

Nest !Int (Doc ann)

Document indented by a number of columns

Union (Doc ann) (Doc ann)

Invariant: The first lines of first document should be longer than the first lines of the second one, so the layout algorithm can pick the one that fits best. Used to implement layout alternatives for group.

Column (Int -> Doc ann)

React on the current cursor position, see column

WithPageWidth (PageWidth -> Doc ann)

React on the document's width, see pageWidth

Nesting (Int -> Doc ann)

React on the current nesting level, see nesting

Annotated ann (Doc ann)

Add an annotation to the enclosed Doc. Can be used for example to add styling directives or alt texts that can then be used by the renderer.

Instances
Functor Doc Source #

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.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

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

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

Show (Doc ann) Source #

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

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

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

show :: Doc ann -> String #

showList :: [Doc ann] -> ShowS #

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

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

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

fromString :: String -> Doc ann #

Generic (Doc ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Associated Types

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

Methods

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

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

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

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

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

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

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

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

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

mempty :: Doc ann #

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

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

type Rep (Doc ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

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

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 #

Convenience function to convert a Showable value /that must not contain newlines/ to a Doc. If there may be newlines, use viaShow instead.

unsafeTextWithoutNewlines :: Text -> Doc ann Source #

(unsafeTextWithoutNewlines s) contains the literal string s.

The string must not contain any newline characters, since this is an invariant of the Doc constructor.

emptyDoc :: Doc ann Source #

The empty document behaves like (pretty ""), so it has a height of 1. This may lead to surprising behaviour if we expect it to bear no weight inside e.g. vcat, where we get an empty line of output from it (parens for visibility only):

>>> vsep ["hello", parens emptyDoc, "world"]
hello
()
world

Together with <>, emptyDoc forms the Monoid Doc.

nest Source #

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

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

line' :: Doc ann Source #

line' is like line, but behaves like mempty if the line break is undone by group (instead of space).

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

softline :: Doc ann Source #

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

softline' :: Doc ann Source #

softline' is like softline, but behaves like mempty if the resulting output does not fit on the page (instead of space). In other words, line is to line' how softline is to softline'.

With enough space, we get direct concatenation:

>>> let doc = "ThisWord" <> softline' <> "IsWayTooLong"
>>> putDocW 80 doc
ThisWordIsWayTooLong

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

>>> putDocW 10 doc
ThisWord
IsWayTooLong
softline' = group line'

hardline :: Doc ann Source #

A hardline is always laid out as a line break, even when grouped 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 doc
lorem ipsum
dolor sit amet
>>> group doc
lorem ipsum
dolor sit amet

group :: Doc ann -> Doc ann Source #

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

changesUponFlattening :: Doc ann -> Maybe (Doc ann) Source #

Choose the first element of each Union, and discard the first field of all FlatAlts.

The result is Just if the element might change depending on the layout algorithm (i.e. contains differently renderable sub-documents), and Nothing if the document is static (e.g. contains only a plain Empty node). See [Group: special flattening] for further explanations.

flatAlt Source #

Arguments

:: Doc ann

Default

-> Doc ann

Fallback when grouped

-> Doc ann 

(flatAlt x fallback) renders as 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 = flatAlt mempty "-"
softline   = flatAlt space line

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

align :: Doc ann -> Doc ann Source #

(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 Source #

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

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

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" <+> align (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 laid out vertically, with separators put in the front:

>>> putDocW 10 doc
list [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 )

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

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

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

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 _ [] = mempty
concatWith (**) [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

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

(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 Source #

(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 Source #

(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 Source #

(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 Source #

(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 Source #

(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 Source #

(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 Source #

(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 Source #

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.

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

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

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

(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

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]

fill Source #

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

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

spaces :: Int -> Doc ann Source #

Insert a number of spaces. Negative values count as 0.

plural Source #

Arguments

:: (Num amount, Eq amount) 
=> doc

1 case

-> doc

other cases

-> amount 
-> doc 

(plural n one many) is 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

enclose Source #

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

surround :: Doc ann -> Doc ann -> Doc ann -> Doc ann Source #

(surround x l r) surrounds document x with l and r.

>>> surround "·" "A" "Z"
A·Z

This is merely an argument reordering of enclose, but allows for definitions like

>>> concatWith (surround ".") ["Data", "Text", "Prettyprint", "Doc"]
Data.Text.Prettyprint.Doc

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

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.

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 Doc tree, including parts that are not rendered due to other layouts fitting better, it is preferrable to reannotate after producing the layout by using reAnnotateS.

Since reAnnotate has the right type and satisfies 'reAnnotate id = id', it is used to define the Functor instance of Doc.

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 Doc tree, including parts that are not rendered due to other layouts fitting better, it is preferrable to reannotate after producing the layout by using alterAnnotationsS.

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

fuse :: FusionDepth -> Doc ann -> Doc ann Source #

(fuse depth doc) combines text nodes so they can be rendered more efficiently. A fused document is always laid out identical to its unfused version.

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

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

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.

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.

>>> defaultLayoutOptions
LayoutOptions {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.

layoutPretty commits to rendering something in a certain way if the next element fits the layout constraints; in other words, it has one SimpleDocStream element lookahead when rendering. Consider using the smarter, but a bit less performant, layoutSmart algorithm if the results seem to run off to the right before having lots of line breaks.

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 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 layoutSmart, fits the layout contstraints:

>>> 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 up to the end of the current indentation level, instead of just having one element lookahead.

layoutWadlerLeijen :: forall ann. FittingPredicate ann -> LayoutOptions -> Doc ann -> SimpleDocStream ann Source #

The Wadler/Leijen layout algorithm

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"])])
>>> doc
lorem
    ipsum
    dolor
        sit
>>> let putDocCompact = renderIO System.IO.stdout . layoutCompact
>>> putDocCompact doc
lorem
ipsum
dolor
sit

renderShowS :: SimpleDocStream ann -> ShowS Source #

Render a SimpleDocStream to a ShowS, useful to write Show instances based on the prettyprinter.

instance Show MyType where
    showsPrec _ = renderShowS . layoutPretty defaultLayoutOptions . pretty