W3cubDocs

/Haskell 8

Text.PrettyPrint.Annotated.HughesPJ

Copyright (c) Trevor Elliott <[email protected]> 2015
License BSD-style (see the file LICENSE)
Maintainer David Terei <[email protected]>
Stability stable
Portability portable
Safe Haskell Safe
Language Haskell98

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.

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
Instances details
Functor Doc
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Eq (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

show :: Doc a -> String Source

showList :: [Doc a] -> ShowS Source

IsString (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

fromString :: String -> Doc a Source

Generic (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

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

Methods

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

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

Semigroup (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

sconcat :: NonEmpty (Doc a) -> Doc a Source

stimes :: Integral b => b -> Doc a -> Doc a Source

Monoid (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

mempty :: Doc a Source

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

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

NFData a => NFData (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnf :: Doc a -> () Source

type Rep (Doc a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

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

data TextDetails Source

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

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.

data AnnotDetails a Source

An annotation (side-metadata) attached at a particular point in a Doc. Allows carrying non-pretty-printed data around in a Doc that is attached at particular points in the structure. Once the Doc is render to an output type (such as String), we can also retrieve where in the rendered document our annotations start and end (see Span and renderSpans).

Instances
Instances details
Functor AnnotDetails
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Eq a => Eq (AnnotDetails a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Show a => Show (AnnotDetails a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

NFData a => NFData (AnnotDetails a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnf :: AnnotDetails a -> () Source

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

maybeParens :: Bool -> Doc a -> Doc a Source

Apply parens to Doc if boolean is true.

maybeBrackets :: Bool -> Doc a -> Doc a Source

Apply brackets to Doc if boolean is true.

maybeBraces :: Bool -> Doc a -> Doc a Source

Apply braces to Doc if boolean is true.

maybeQuotes :: Bool -> Doc a -> Doc a Source

Apply quotes to Doc if boolean is true.

maybeDoubleQuotes :: Bool -> Doc a -> Doc a Source

Apply doubleQuotes to Doc if boolean is true.

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

Utility functions for documents

first :: Doc a -> Doc a -> Doc a Source

first returns its first argument if it is non-empty, otherwise its second.

reduceDoc :: Doc a -> RDoc a Source

Perform some simplification of a built up GDoc.

Rendering documents

Default rendering

render :: Doc a -> String Source

Render the Doc to a String using the default Style (see style).

Annotation rendering

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

Render an annotated Doc to a String and list of annotations (see Span) using the default Style (see style).

data Span a Source

A Span represents the result of an annotation after a Doc has been rendered, capturing where the annotation now starts and ends in the rendered output.

Constructors

Span

Fields

Instances
Instances details
Functor Span
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Eq a => Eq (Span a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show a => Show (Span a)
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

show :: Span a -> String Source

showList :: [Span a] -> ShowS Source

renderDecorated Source

Arguments

:: (ann -> String)

Starting an annotation.

-> (ann -> String)

Ending an annotation.

-> Doc ann
-> String

Render out a String, interpreting the annotations as part of the resulting document.

IMPORTANT: the size of the annotation string does NOT figure into the layout of the document, so the document will lay out as though the annotations are not present.

renderDecoratedM Source

Arguments

:: Monad m
=> (ann -> m r)

Starting an annotation.

-> (ann -> m r)

Ending an annotation.

-> (String -> m r)

Text formatting.

-> m r

Document end.

-> Doc ann
-> m r

Render a document with annotations, by interpreting the start and end of the annotations, as well as the text details in the context of a monad.

Rendering with a particular style

data Style Source

A rendering style. Allows us to specify constraints to choose among the many different rendering options.

Constructors

Style

Fields

  • mode :: Mode

    The rendering mode.

  • lineLength :: Int

    Maximum length of a line, in characters.

  • ribbonsPerLine :: Float

    Ratio of line length to ribbon length. A ribbon refers to the characters on a line excluding indentation. So a lineLength of 100, with a ribbonsPerLine of 2.0 would only allow up to 50 characters of ribbon to be displayed on a line, while allowing it to be indented up to 50 characters.

Instances
Instances details
Eq Style
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show Style
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Generic Style
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type Source

Methods

from :: Style -> Rep Style x Source

to :: Rep Style x -> Style Source

type Rep Style
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Style = D1 ('MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) (S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mode) :*: (S1 ('MetaSel ('Just "lineLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "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.

data Mode Source

Rendering mode.

Constructors

PageMode

Normal rendering (lineLength and ribbonsPerLine respected').

ZigZagMode

With zig-zag cuts.

LeftMode

No indentation, infinitely long lines (lineLength ignored), but explicit new lines, i.e., text "one" $$ text "two", are respected.

OneLineMode

All on one line, lineLength ignored and explicit new lines ($$) are turned into spaces.

Instances
Instances details
Eq Mode
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show Mode
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Generic Mode
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type Source

Methods

from :: Mode -> Rep Mode x Source

to :: Rep Mode x -> Mode Source

type Rep Mode
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

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

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. Please refer to the Style and Mode types for a description of rendering mode, line length and ribbons.

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.

The general rendering interface, supporting annotations. Please refer to the Style and Mode types for a description of rendering mode, line length and ribbons.

© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.8.3/docs/html/libraries/pretty-1.1.3.6/Text-PrettyPrint-Annotated-HughesPJ.html