pretty-1.1.3.2: Pretty-printing library

Copyright(c) Trevor Elliott <revor@galois.com> 2015
LicenseBSD-style (see the file LICENSE)
MaintainerDavid Terei <code@davidterei.com>
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Text.PrettyPrint.Annotated

Contents

Description

This module provides a version of pretty that allows for annotations to be attached to documents. Annotations are arbitrary pieces of metadata that can be attached to sub-documents.

This module should be used as opposed to the HughesPJ module. Both are equivalent though as this module simply re-exports the other.

Synopsis

The document type

data Doc a Source

The abstract type of documents. A Doc represents a *set* of layouts. A Doc with no occurrences of Union or NoDoc represents just one layout.

Instances

Functor Doc 

Methods

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

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

Eq (Doc a) 

Methods

(==) :: Doc a -> Doc a -> Bool Source

(/=) :: Doc a -> Doc a -> Bool Source

Show (Doc a) 

Methods

showsPrec :: Int -> Doc a -> ShowS Source

show :: Doc a -> String Source

showList :: [Doc a] -> ShowS Source

IsString (Doc a) 

Methods

fromString :: String -> Doc a Source

Generic (Doc a) 

Associated Types

type Rep (Doc a) :: * -> * Source

Methods

from :: Doc a -> Rep (Doc a) x Source

to :: Rep (Doc a) x -> Doc a Source

Monoid (Doc a) 

Methods

mempty :: Doc a Source

mappend :: Doc a -> Doc a -> Doc a Source

mconcat :: [Doc a] -> Doc a Source

NFData a => NFData (Doc a) 

Methods

rnf :: Doc a -> () Source

type Rep (Doc a) = D1 (MetaData "Doc" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.2" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Empty" PrefixI False) U1) (C1 (MetaCons "NilAbove" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))))) ((:+:) (C1 (MetaCons "TextBeside" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (AnnotDetails a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))))) (C1 (MetaCons "Nest" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))))))) ((:+:) ((:+:) (C1 (MetaCons "Union" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))))) (C1 (MetaCons "NoDoc" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Beside" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a)))))) (C1 (MetaCons "Above" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc a))))))))) 

Constructing documents

Converting values into documents

char :: Char -> Doc a Source

A document of height and width 1, containing a literal character.

text :: String -> Doc a Source

A document of height 1 containing a literal string. text satisfies the following laws:

The side condition on the last law is necessary because text "" has height 1, while empty has no height.

ptext :: String -> Doc a Source

Same as text. Used to be used for Bytestrings.

sizedText :: Int -> String -> Doc a Source

Some text with any width. (text s = sizedText (length s) s)

zeroWidthText :: String -> Doc a Source

Some text, but without any width. Use for non-printing text such as a HTML or Latex tags

int Source

Arguments

:: Int 
-> Doc a
int n = text (show n)

integer Source

Arguments

:: Integer 
-> Doc a
integer n = text (show n)

float Source

Arguments

:: Float 
-> Doc a
float n = text (show n)

double Source

Arguments

:: Double 
-> Doc a
double n = text (show n)

rational Source

Arguments

:: Rational 
-> Doc a
rational n = text (show n)

Simple derived documents

semi Source

Arguments

:: Doc a

A ';' character

comma Source

Arguments

:: Doc a

A ',' character

colon Source

Arguments

:: Doc a

A : character

space Source

Arguments

:: Doc a

A space character

equals Source

Arguments

:: Doc a

A '=' character

lparen Source

Arguments

:: Doc a

A '(' character

rparen Source

Arguments

:: Doc a

A ')' character

lbrack Source

Arguments

:: Doc a

A '[' character

rbrack Source

Arguments

:: Doc a

A ']' character

lbrace Source

Arguments

:: Doc a

A '{' character

rbrace Source

Arguments

:: Doc a

A '}' character

Wrapping documents in delimiters

parens Source

Arguments

:: Doc a 
-> Doc a

Wrap document in (...)

brackets Source

Arguments

:: Doc a 
-> Doc a

Wrap document in [...]

braces Source

Arguments

:: Doc a 
-> Doc a

Wrap document in {...}

quotes Source

Arguments

:: Doc a 
-> Doc a

Wrap document in '...'

doubleQuotes Source

Arguments

:: Doc a 
-> Doc a

Wrap document in "..."

Combining documents

empty :: Doc a Source

The empty document, with no height and no width. empty is the identity for <>, <+>, $$ and $+$, and anywhere in the argument list for sep, hcat, hsep, vcat, fcat etc.

(<>) :: Doc a -> Doc a -> Doc a infixl 6 Source

Beside. <> is associative, with identity empty.

(<+>) :: Doc a -> Doc a -> Doc a infixl 6 Source

Beside, separated by space, unless one of the arguments is empty. <+> is associative, with identity empty.

hcat :: [Doc a] -> Doc a Source

List version of <>.

hsep :: [Doc a] -> Doc a Source

List version of <+>.

($$) :: Doc a -> Doc a -> Doc a infixl 5 Source

Above, except that if the last line of the first argument stops at least one position before the first line of the second begins, these two lines are overlapped. For example:

   text "hi" $$ nest 5 (text "there")

lays out as

   hi   there

rather than

   hi
        there

$$ is associative, with identity empty, and also satisfies

  • (x $$ y) <> z = x $$ (y <> z), if y non-empty.

($+$) :: Doc a -> Doc a -> Doc a infixl 5 Source

Above, with no overlapping. $+$ is associative, with identity empty.

vcat :: [Doc a] -> Doc a Source

List version of $$.

sep :: [Doc a] -> Doc a Source

Either hsep or vcat.

cat :: [Doc a] -> Doc a Source

Either hcat or vcat.

fsep :: [Doc a] -> Doc a Source

"Paragraph fill" version of sep.

fcat :: [Doc a] -> Doc a Source

"Paragraph fill" version of cat.

nest :: Int -> Doc a -> Doc a Source

Nest (or indent) a document by a given number of positions (which may also be negative). nest satisfies the laws:

The side condition on the last law is needed because empty is a left identity for <>.

hang :: Doc a -> Int -> Doc a -> Doc a Source

hang d1 n d2 = sep [d1, nest n d2]

punctuate :: Doc a -> [Doc a] -> [Doc a] Source

punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]

Annotating documents

annotate :: a -> Doc a -> Doc a Source

Attach an annotation to a document.

Predicates on documents

isEmpty :: Doc a -> Bool Source

Returns True if the document is empty

Rendering documents

Default rendering

render :: Doc a -> String Source

Render the Doc to a String using the default Style.

Annotation rendering

renderSpans :: Doc ann -> (String, [Span ann]) Source

data Span a Source

Constructors

Span 

Instances

Functor Span 

Methods

fmap :: (a -> b) -> Span a -> Span b Source

(<$) :: a -> Span b -> Span a Source

Eq a => Eq (Span a) 

Methods

(==) :: Span a -> Span a -> Bool Source

(/=) :: Span a -> Span a -> Bool Source

Show a => Show (Span a) 

Rendering with a particular style

data Style Source

A rendering style.

Constructors

Style 

Fields

Instances

Eq Style 

Methods

(==) :: Style -> Style -> Bool Source

(/=) :: Style -> Style -> Bool Source

Show Style 
Generic Style 

Associated Types

type Rep Style :: * -> * Source

Methods

from :: Style -> Rep Style x Source

to :: Rep Style x -> Style Source

type Rep Style = D1 (MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.2" False) (C1 (MetaCons "Style" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mode)) ((:*:) (S1 (MetaSel (Just Symbol "lineLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "ribbonsPerLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))))) 

style :: Style Source

The default style (mode=PageMode, lineLength=100, ribbonsPerLine=1.5).

renderStyle :: Style -> Doc a -> String Source

Render the Doc to a String using the given Style.

General rendering

fullRender Source

Arguments

:: Mode

Rendering mode

-> Int

Line length

-> Float

Ribbons per line

-> (TextDetails -> a -> a)

What to do with text

-> a

What to do at the end

-> Doc b

The document

-> a

Result

The general rendering interface.

fullRenderAnn Source

Arguments

:: Mode

Rendering mode

-> Int

Line length

-> Float

Ribbons per line

-> (AnnotDetails b -> a -> a)

What to do with text

-> a

What to do at the end

-> Doc b

The document

-> a

Result

data Mode Source

Rendering mode.

Constructors

PageMode

Normal

ZigZagMode

With zig-zag cuts

LeftMode

No indentation, infinitely long lines

OneLineMode

All on one line

Instances

Eq Mode 

Methods

(==) :: Mode -> Mode -> Bool Source

(/=) :: Mode -> Mode -> Bool Source

Show Mode 
Generic Mode 

Associated Types

type Rep Mode :: * -> * Source

Methods

from :: Mode -> Rep Mode x Source

to :: Rep Mode x -> Mode Source

type Rep Mode = D1 (MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.2" False) ((:+:) ((:+:) (C1 (MetaCons "PageMode" PrefixI False) U1) (C1 (MetaCons "ZigZagMode" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LeftMode" PrefixI False) U1) (C1 (MetaCons "OneLineMode" PrefixI False) U1))) 

data TextDetails Source

The TextDetails data type

A TextDetails represents a fragment of text that will be output at some point.

Constructors

Chr !Char

A single Char fragment

Str String

A whole String fragment

PStr String

Used to represent a Fast String fragment but now deprecated and identical to the Str constructor.