wl-pprint-annotated-0.0.1.1: Wadler/Leijen pretty printer with annotations and slightly modernized API

CopyrightGoogle Inc. (c) 2013
Edward Kmett (c) 2011
Daan Leijen (c) 2000
LicenseBSD-style (see the file LICENSE)
Maintainermail@daniel-mendler.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Text.PrettyPrint.Annotated.WL

Contents

Description

Pretty print module based on Daan Leijen's implementation of Philip Wadler's "prettier printer"

     "A prettier printer"
     Draft paper, April 1997, revised March 1998.
     http://homepages.inf.ed.ac.uk/wadler/papers/prettier/prettier.pdf

This is an implementation of the pretty printing combinators described by Philip Wadler (1997). In their bare essence, the combinators of Wadler are not expressive enough to describe some commonly occurring layouts. The PPrint library adds new primitives to describe these layouts and works well in practice.

The library is based on a single way to concatenate documents, which is associative and has both a left and right unit. This simple design leads to an efficient and short implementation. The simplicity is reflected in the predictable behaviour of the combinators which make them easy to use in practice.

A thorough description of the primitive combinators and their implementation can be found in Philip Wadler's paper (1997). Additions and the main differences with his original paper are:

  • The nil document is called mempty.
  • The operator </> is used for soft line breaks.
  • There are three new primitives: align, fill and fillBreak. These are very useful in practice.
  • Lots of other useful combinators, like fillSep and list.
  • There are two renderers, renderPretty for pretty printing and renderCompact for compact output. The pretty printing algorithm also uses a ribbon-width now for even prettier output.
  • There are two display routines, displayS for strings and displayIO for file based output.
  • There is a Pretty class.
  • The implementation uses optimised representations and strictness annotations.

Synopsis

Documents

data ADoc a Source #

The abstract data type Doc represents pretty documents.

Doc is an instance of the Show class. (show doc) pretty prints document doc with a page width of 100 characters and a ribbon width of 40 characters.

show (text "hello" <#> text "world")

Which would return the string "hello\nworld", i.e.

hello
world

Constructors

Empty 
Char !Char 
Text !Int String 
Line 
FlatAlt (ADoc a) (ADoc a) 
Cat (ADoc a) (ADoc a) 
Nest !Int (ADoc a) 
Union (ADoc a) (ADoc a) 
Annotate a (ADoc a) 
Column (Int -> ADoc a) 
Nesting (Int -> ADoc a) 
Columns (Maybe Int -> ADoc a) 
Ribbon (Maybe Int -> ADoc a) 

Instances

Functor ADoc Source # 

Methods

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

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

Show (ADoc a) Source # 

Methods

showsPrec :: Int -> ADoc a -> ShowS #

show :: ADoc a -> String #

showList :: [ADoc a] -> ShowS #

IsString (ADoc a) Source # 

Methods

fromString :: String -> ADoc a #

Generic (ADoc a) Source # 

Associated Types

type Rep (ADoc a) :: * -> * #

Methods

from :: ADoc a -> Rep (ADoc a) x #

to :: Rep (ADoc a) x -> ADoc a #

Semigroup (ADoc a) Source # 

Methods

(<>) :: ADoc a -> ADoc a -> ADoc a #

sconcat :: NonEmpty (ADoc a) -> ADoc a #

stimes :: Integral b => b -> ADoc a -> ADoc a #

Monoid (ADoc a) Source # 

Methods

mempty :: ADoc a #

mappend :: ADoc a -> ADoc a -> ADoc a #

mconcat :: [ADoc a] -> ADoc a #

NFData a => NFData (ADoc a) Source # 

Methods

rnf :: ADoc a -> () #

Pretty (ADoc a) Source # 

Methods

pretty :: ADoc a -> ADoc b Source #

prettyList :: [ADoc a] -> ADoc b Source #

type Rep (ADoc a) Source # 
type Rep (ADoc a) = D1 (MetaData "ADoc" "Text.PrettyPrint.Annotated.WL" "wl-pprint-annotated-0.0.1.1-gVUrtpcDtlEjujzZVBXgI" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Empty" PrefixI False) U1) ((:+:) (C1 (MetaCons "Char" PrefixI False) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Char))) (C1 (MetaCons "Text" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) ((:+:) (C1 (MetaCons "Line" PrefixI False) U1) ((:+:) (C1 (MetaCons "FlatAlt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a))))) (C1 (MetaCons "Cat" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a)))))))) ((:+:) ((:+:) (C1 (MetaCons "Nest" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a))))) ((:+:) (C1 (MetaCons "Union" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a))))) (C1 (MetaCons "Annotate" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ADoc a))))))) ((:+:) ((:+:) (C1 (MetaCons "Column" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> ADoc a)))) (C1 (MetaCons "Nesting" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> ADoc a))))) ((:+:) (C1 (MetaCons "Columns" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int -> ADoc a)))) (C1 (MetaCons "Ribbon" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int -> ADoc a))))))))

putDoc :: ADoc a -> IO () Source #

The action (putDoc doc) pretty prints document doc to the standard output, with a page width of 100 characters and a ribbon width of 40 characters.

main :: IO ()
main = do{ putDoc (text "hello" <+> text "world") }

Which would output

hello world

hPutDoc :: Handle -> ADoc a -> IO () Source #

(hPutDoc handle doc) pretty prints document doc to the file handle handle with a page width of 100 characters and a ribbon width of 40 characters.

main = do{ handle <- openFile "MyFile" WriteMode
         ; hPutDoc handle (vcat (map text
                           ["vertical","text"]))
         ; hClose handle
         }

Basic combinators

char :: Char -> ADoc a Source #

The document (char c) contains the literal character c. The character shouldn't be a newline ('\n'), the function line should be used for line breaks.

text :: String -> ADoc a Source #

The document (text s) contains the literal string s. The string shouldn't contain any newline ('\n') characters. If the string contains newline characters, the function pretty should be used.

nest :: Int -> ADoc a -> ADoc a Source #

The document (nest i x) renders document x with the current indentation level increased by i (See also hang, align and indent).

nest 2 (text "hello" <#> text "world") <#> text "!"

outputs as:

hello
  world
!

line :: ADoc a Source #

The line document advances to the next line and indents to the current nesting level. Document line behaves like (text " ") if the line break is undone by group.

linebreak :: ADoc a Source #

The linebreak document advances to the next line and indents to the current nesting level. Document linebreak behaves like mempty if the line break is undone by group.

group :: ADoc a -> ADoc a Source #

The group combinator is used to specify alternative layouts. The document (group x) undoes all line breaks in document x. The resulting line is added to the current line if that fits the page. Otherwise, the document x is rendered without any changes.

softline :: ADoc a Source #

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

softline = group line

softbreak :: ADoc a Source #

The document softbreak behaves like mempty if the resulting output fits the page, otherwise it behaves like line.

softbreak  = group linebreak

hardline :: ADoc a Source #

A linebreak that can not be flattened; it is guaranteed to be rendered as a newline.

flatAlt :: ADoc a -> ADoc a -> ADoc a Source #

flatAlt creates a document that changes when flattened; normally it is rendered as the first argument, but when flattened is rendered as the second.

Annotations

annotate :: a -> ADoc a -> ADoc a Source #

docMapAnn Source #

Arguments

:: (a -> ADoc a' -> ADoc a')

Annotate

-> ADoc a 
-> ADoc a' 

simpleDocMapAnn Source #

Arguments

:: (r -> a -> r)

SPushAnn state merge

-> (r -> SimpleDoc a' -> SimpleDoc a')

SPushAnn processor

-> (r -> SimpleDoc a' -> SimpleDoc a')

SPopAnn processor

-> r

Initial state

-> SimpleDoc a 
-> SimpleDoc a' 

simpleDocScanAnn :: (r -> a -> r) -> r -> SimpleDoc a -> SimpleDoc r Source #

Alignment

align :: ADoc a -> ADoc a Source #

The document (align x) renders 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:

x $$ y = align (x <#> y)
test = text "hi" <+> (text "nice" $$ text "world")

which will be layed out as:

hi nice
   world

hang :: Int -> ADoc a -> ADoc a Source #

The hang combinator implements hanging indentation. The document (hang i x) renders document x with a nesting level set to the current column plus i. The following example uses hanging indentation for some text:

test  = hang 4 (fillSep (map text
        (words "the hang combinator indents these words !")))

Which lays out on a page with a width of 20 characters as:

the hang combinator
    indents these
    words !

The hang combinator is implemented as:

hang i x  = align (nest i x)

indent :: Int -> ADoc a -> ADoc a Source #

The document (indent i x) indents document x with i spaces.

test  = indent 4 (fillSep (map text
        (words "the indent combinator indents these words !")))

Which lays out with a page width of 20 as:

    the indent
    combinator
    indents these
    words !

encloseSep :: Foldable f => ADoc a -> ADoc a -> ADoc a -> f (ADoc a) -> ADoc a Source #

The document (encloseSep l r sep xs) concatenates the documents xs separated by sep and encloses the resulting document by l and r. The documents are rendered horizontally if that fits the page. Otherwise they are aligned vertically. All separators are put in front of the elements. For example, the combinator list can be defined with encloseSep:

list xs = encloseSep lbracket rbracket comma xs
test    = text "list" <+> (list (map int [10,200,3000]))

Which is layed out with a page width of 20 as:

list [10, 200, 3000]

But when the page width is 15, it is layed out as:

list [ 10
     , 200
     , 3000 ]

list :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (list xs) comma separates the documents xs and encloses them in square brackets. The documents are rendered horizontally if that fits the page. Otherwise they are aligned vertically. All comma separators are put in front of the elements.

tupled :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (tupled xs) comma separates the documents xs and encloses them in parenthesis. The documents are rendered horizontally if that fits the page. Otherwise they are aligned vertically. All comma separators are put in front of the elements.

semiBraces :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (semiBraces xs) separates the documents xs with semi colons and encloses them in braces. The documents are rendered horizontally if that fits the page. Otherwise they are aligned vertically. All semi colons are put in front of the elements.

Operators

(<+>) :: ADoc a -> ADoc a -> ADoc a infixr 6 Source #

(</>) :: ADoc a -> ADoc a -> ADoc a infixr 5 Source #

The document (x </> y) concatenates document x and y with a softline in between. This effectively puts x and y either next to each other (with a space in between) or underneath each other. (infixr 5)

(<//>) :: ADoc a -> ADoc a -> ADoc a infixr 5 Source #

The document (x <//> y) concatenates document x and y with a softbreak in between. This effectively puts x and y either right next to each other or underneath each other. (infixr 5)

(<#>) :: ADoc a -> ADoc a -> ADoc a infixr 5 Source #

The document (x <#> y) concatenates document x and y with a line in between. (infixr 5)

(<##>) :: ADoc a -> ADoc a -> ADoc a infixr 5 Source #

The document (x <##> y) concatenates document x and y with a linebreak in between. (infixr 5)

List combinators

hsep :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (hsep xs) concatenates all documents xs horizontally with (<+>).

vsep :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (vsep xs) concatenates all documents xs vertically with (<#>). If a group undoes the line breaks inserted by vsep, all documents are separated with a space.

someText = map text (words ("text to lay out"))

test     = text "some" <+> vsep someText

This is layed out as:

some text
to
lay
out

The align combinator can be used to align the documents under their first element

test = text "some" <+> align (vsep someText)

Which is printed as:

some text
     to
     lay
     out

fillSep :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (fillSep xs) concatenates documents xs horizontally with (<+>) as long as its fits the page, then inserts a line and continues doing that for all documents in xs.

fillSep xs  = foldr (</>) mempty xs

sep :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (sep xs) concatenates all documents xs either horizontally with (<+>), if it fits the page, or vertically with (<#>).

sep xs  = group (vsep xs)

hcat :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (hcat xs) concatenates all documents xs horizontally with (<>).

vcat :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (vcat xs) concatenates all documents xs vertically with (<##>). If a group undoes the line breaks inserted by vcat, all documents are directly concatenated.

fillCat :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (fillCat xs) concatenates documents xs horizontally with (<>) as long as its fits the page, then inserts a linebreak and continues doing that for all documents in xs.

fillCat xs  = foldr (<//>) mempty xs

cat :: Foldable f => f (ADoc a) -> ADoc a Source #

The document (cat xs) concatenates all documents xs either horizontally with (<>), if it fits the page, or vertically with (<##>).

cat xs  = group (vcat xs)

punctuate :: Traversable f => ADoc a -> f (ADoc a) -> f (ADoc a) Source #

(punctuate p xs) concatenates all documents in xs with document p except for the last document.

someText = map text ["words","in","a","tuple"]
test     = parens (align (cat (punctuate comma someText)))

This is layed out on a page width of 20 as:

(words,in,a,tuple)

But when the page width is 15, it is layed out as:

(words,
 in,
 a,
 tuple)

(If you want put the commas in front of their elements instead of at the end, you should use tupled or, in general, encloseSep.)

Fillers

fill :: Int -> ADoc a -> ADoc a Source #

The document (fill i x) renders 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 combinator is quite useful in practice to output a list of bindings. The following example demonstrates this.

types  = [("mempty","Doc a")
         ,("nest","Int -> ADoc a -> ADoc a")
         ,("linebreak","Doc a")]

ptype (name,tp)
       = fill 6 (text name) <+> text "::" <+> text tp

test   = text "let" <+> align (vcat (map ptype types))

Which is layed out as:

let mempty  :: ADoc a
    nest   :: Int -> ADoc a -> ADoc a
    linebreak :: ADoc a

fillBreak :: Int -> ADoc a -> ADoc a Source #

The document (fillBreak i x) first renders 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 previous example to use fillBreak, we get a useful variation of the previous output:

ptype (name,tp)
       = fillBreak 6 (text name) <+> text "::" <+> text tp

The output will now be:

let mempty  :: ADoc a
    nest   :: Int -> ADoc a -> ADoc a
    linebreak
           :: ADoc a

Bracketing combinators

enclose :: ADoc a -> ADoc a -> ADoc a -> ADoc a Source #

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

enclose l r x   = l <> x <> r

squotes :: ADoc a -> ADoc a Source #

Document (squotes x) encloses document x with single quotes "'".

dquotes :: ADoc a -> ADoc a Source #

Document (dquotes x) encloses document x with double quotes '"'.

parens :: ADoc a -> ADoc a Source #

Document (parens x) encloses document x in parenthesis, "(" and ")".

angles :: ADoc a -> ADoc a Source #

Document (angles x) encloses document x in angles, "<" and ">".

braces :: ADoc a -> ADoc a Source #

Document (braces x) encloses document x in braces, "{" and "}".

brackets :: ADoc a -> ADoc a Source #

Document (brackets x) encloses document x in square brackets, "[" and "]".

Character documents

lparen :: ADoc a Source #

The document lparen contains a left parenthesis, "(".

rparen :: ADoc a Source #

The document rparen contains a right parenthesis, ")".

langle :: ADoc a Source #

The document langle contains a left angle, "<".

rangle :: ADoc a Source #

The document rangle contains a right angle, ">".

lbrace :: ADoc a Source #

The document lbrace contains a left brace, "{".

rbrace :: ADoc a Source #

The document rbrace contains a right brace, "}".

lbracket :: ADoc a Source #

The document lbracket contains a left square bracket, "[".

rbracket :: ADoc a Source #

The document rbracket contains a right square bracket, "]".

squote :: ADoc a Source #

The document squote contains a single quote, "'".

dquote :: ADoc a Source #

The document dquote contains a double quote, '"'.

semi :: ADoc a Source #

The document semi contains a semi colon, ";".

colon :: ADoc a Source #

The document colon contains a colon, ":".

comma :: ADoc a Source #

The document comma contains a comma, ",".

space :: ADoc a Source #

The document space contains a single space, " ".

x <+> y   = x <> space <> y

dot :: ADoc a Source #

The document dot contains a single dot, ".".

backslash :: ADoc a Source #

The document backslash contains a back slash, "\".

equals :: ADoc a Source #

The document equals contains an equal sign, "=".

Pretty class

class Pretty a where Source #

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

Methods

pretty :: a -> ADoc b Source #

prettyList :: [a] -> ADoc b Source #

pretty :: Show a => a -> ADoc b Source #

Instances

Pretty Bool Source # 

Methods

pretty :: Bool -> ADoc b Source #

prettyList :: [Bool] -> ADoc b Source #

Pretty Char Source # 

Methods

pretty :: Char -> ADoc b Source #

prettyList :: [Char] -> ADoc b Source #

Pretty Double Source # 
Pretty Float Source # 

Methods

pretty :: Float -> ADoc b Source #

prettyList :: [Float] -> ADoc b Source #

Pretty Int Source # 

Methods

pretty :: Int -> ADoc b Source #

prettyList :: [Int] -> ADoc b Source #

Pretty Int8 Source # 

Methods

pretty :: Int8 -> ADoc b Source #

prettyList :: [Int8] -> ADoc b Source #

Pretty Int16 Source # 

Methods

pretty :: Int16 -> ADoc b Source #

prettyList :: [Int16] -> ADoc b Source #

Pretty Int32 Source # 

Methods

pretty :: Int32 -> ADoc b Source #

prettyList :: [Int32] -> ADoc b Source #

Pretty Int64 Source # 

Methods

pretty :: Int64 -> ADoc b Source #

prettyList :: [Int64] -> ADoc b Source #

Pretty Integer Source # 
Pretty Rational Source # 
Pretty Word Source # 

Methods

pretty :: Word -> ADoc b Source #

prettyList :: [Word] -> ADoc b Source #

Pretty Word8 Source # 

Methods

pretty :: Word8 -> ADoc b Source #

prettyList :: [Word8] -> ADoc b Source #

Pretty Word16 Source # 
Pretty Word32 Source # 
Pretty Word64 Source # 
Pretty () Source # 

Methods

pretty :: () -> ADoc b Source #

prettyList :: [()] -> ADoc b Source #

Pretty Natural Source # 
Pretty Text Source # 

Methods

pretty :: Text -> ADoc b Source #

prettyList :: [Text] -> ADoc b Source #

Pretty Text Source # 

Methods

pretty :: Text -> ADoc b Source #

prettyList :: [Text] -> ADoc b Source #

Pretty a => Pretty [a] Source # 

Methods

pretty :: [a] -> ADoc b Source #

prettyList :: [[a]] -> ADoc b Source #

Pretty a => Pretty (Maybe a) Source # 

Methods

pretty :: Maybe a -> ADoc b Source #

prettyList :: [Maybe a] -> ADoc b Source #

Pretty a => Pretty (NonEmpty a) Source # 

Methods

pretty :: NonEmpty a -> ADoc b Source #

prettyList :: [NonEmpty a] -> ADoc b Source #

Pretty a => Pretty (Seq a) Source # 

Methods

pretty :: Seq a -> ADoc b Source #

prettyList :: [Seq a] -> ADoc b Source #

Pretty (ADoc a) Source # 

Methods

pretty :: ADoc a -> ADoc b Source #

prettyList :: [ADoc a] -> ADoc b Source #

(Pretty a, Pretty b) => Pretty (a, b) Source # 

Methods

pretty :: (a, b) -> ADoc b Source #

prettyList :: [(a, b)] -> ADoc b Source #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) Source # 

Methods

pretty :: (a, b, c) -> ADoc b Source #

prettyList :: [(a, b, c)] -> ADoc b Source #

Rendering

data SimpleDoc a Source #

The data type SimpleDoc represents rendered documents and is used by the display functions.

The Int in SText contains the length of the string. The Int in SLine contains the indentation for that line. The library provides two default display functions displayS and displayIO. You can provide your own display function by writing a function from a SimpleDoc to your own output format.

Instances

Functor SimpleDoc Source # 

Methods

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

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

Foldable SimpleDoc Source # 

Methods

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

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

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

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

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

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

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

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

toList :: SimpleDoc a -> [a] #

null :: SimpleDoc a -> Bool #

length :: SimpleDoc a -> Int #

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

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

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

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

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

Traversable SimpleDoc Source # 

Methods

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

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

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

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

Generic (SimpleDoc a) Source # 

Associated Types

type Rep (SimpleDoc a) :: * -> * #

Methods

from :: SimpleDoc a -> Rep (SimpleDoc a) x #

to :: Rep (SimpleDoc a) x -> SimpleDoc a #

NFData a => NFData (SimpleDoc a) Source # 

Methods

rnf :: SimpleDoc a -> () #

type Rep (SimpleDoc a) Source # 
type Rep (SimpleDoc a) = D1 (MetaData "SimpleDoc" "Text.PrettyPrint.Annotated.WL" "wl-pprint-annotated-0.0.1.1-gVUrtpcDtlEjujzZVBXgI" False) ((:+:) ((:+:) (C1 (MetaCons "SEmpty" PrefixI False) U1) ((:+:) (C1 (MetaCons "SChar" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Char)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDoc a))))) (C1 (MetaCons "SText" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDoc a)))))))) ((:+:) (C1 (MetaCons "SLine" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDoc a))))) ((:+:) (C1 (MetaCons "SPushAnn" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDoc a))))) (C1 (MetaCons "SPopAnn" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SimpleDoc a))))))))

renderPretty :: Float -> Int -> ADoc a -> SimpleDoc a Source #

This is the default pretty printer which is used by show, putDoc and hPutDoc. (renderPretty ribbonfrac width x) renders document x with a page width of width and a ribbon width of (ribbonfrac * width) characters. The ribbon width is the maximal amount of non-indentation characters on a line. The parameter ribbonfrac should be between 0.0 and 1.0. If it is lower or higher, the ribbon width will be 0 or width respectively.

renderCompact :: ADoc a -> SimpleDoc a Source #

(renderCompact x) renders document x without adding any indentation. Since no 'pretty' printing is involved, this renderer is very fast. The resulting output contains fewer characters than a pretty printed version and can be used for output that is read by other programs.

renderSmart :: Int -> ADoc a -> SimpleDoc a Source #

A slightly smarter rendering algorithm with more lookahead. It provides provide earlier breaking on deeply nested structures. For example, consider this python-ish pseudocode: fun(fun(fun(fun(fun([abcdefg, abcdefg]))))) If we put a softbreak (+ nesting 2) after each open parenthesis, and align the elements of the list to match the opening brackets, this will render with renderPretty and a page width of 20c as: fun(fun(fun(fun(fun([ | abcdef, | abcdef, ] ))))) | Where the 20c. boundary has been marked with |. Because renderPretty only uses one-line lookahead, it sees that the first line fits, and is stuck putting the second and third lines after the 20c mark. In contrast, renderSmart will continue to check the potential document up to the end of the indentation level. Thus, it will format the document as:

fun(                |
  fun(              |
    fun(            |
      fun(          |
        fun([       |
              abcdef,
              abcdef,
            ]       |
  )))))             |

Which fits within the 20c. mark. In addition, renderSmart uses this lookahead to minimize the number of lines printed, leading to more compact and visually appealing output. Consider this example using the same syntax as above: aaaaaaaaaaa([abc, def, ghi]) When rendered with renderPretty and a page width of 20c, we get: aaaaaaaaaaa([ abc , def , ghi ]) Whereas when rendered with renderSmart and a page width of 20c, we get: aaaaaaaaaaa( [abc, def, ghi])

displayS :: SimpleDoc a -> ShowS Source #

(displayS simpleDoc) takes the output simpleDoc from a rendering function and transforms it to a ShowS type (for use in the Show class). Along the way, all annotations are discarded.

showWidth :: Int -> ADoc -> String
showWidth w x   = displayS (renderPretty 0.4 w x) ""

displayIO :: Handle -> SimpleDoc a -> IO () Source #

(displayIO handle simpleDoc) writes simpleDoc to the file handle handle, discarding all annotations. This function is used for example by hPutDoc:

hPutDoc handle doc  = displayIO handle (renderPretty 0.4 100 doc)

displayDecoratedA Source #

Arguments

:: (Applicative f, Monoid o) 
=> (a -> f o)

How to push an annotated region

-> (a -> f o)

How to end an annotated region

-> (String -> f o)

How to display a string (from document or whitespace)

-> SimpleDoc a 
-> f o 

Display a rendered document.

This function takes a means of pushing an annotated region, a means of ending it, and a means of displaying a string, with effects f to display or compute the output o.

displayDecorated Source #

Arguments

:: Monoid o 
=> (a -> o)

How to push an annotated region

-> (a -> o)

How to end an annotated region

-> (String -> o)

How to display a string (from document or whitespace)

-> SimpleDoc a 
-> o 

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

displaySpans :: Monoid o => (String -> o) -> SimpleDoc a -> (o, SpanList a) Source #

Generate a pair of a string and a list of source span/annotation pairs

Undocumented

column :: (Int -> ADoc a) -> ADoc a Source #

nesting :: (Int -> ADoc a) -> ADoc a Source #

width :: ADoc a -> (Int -> ADoc a) -> ADoc a Source #

columns :: (Maybe Int -> ADoc a) -> ADoc a Source #

ribbon :: (Maybe Int -> ADoc a) -> ADoc a Source #

Re-exported standard functions

mempty :: Monoid a => a #

Identity of mappend

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

An associative operation.

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

If a is also a Monoid we further require

(<>) = mappend