| Safe Haskell | None | 
|---|
Text.PrettyPrint.Annotated.Leijen
Contents
- data Doc a
- putDoc :: Doc a -> IO ()
- hPutDoc :: Handle -> Doc a -> IO ()
- empty :: Doc a
- char :: Char -> Doc a
- text :: String -> Doc a
- (<>) :: Doc a -> Doc a -> Doc a
- nest :: Int -> Doc a -> Doc a
- line :: Doc a
- linebreak :: Doc a
- group :: Doc a -> Doc a
- softline :: Doc a
- softbreak :: Doc a
- align :: Doc a -> Doc a
- hang :: Int -> Doc a -> Doc a
- indent :: Int -> Doc a -> Doc a
- encloseSep :: Doc a -> Doc a -> Doc a -> [Doc a] -> Doc a
- list :: [Doc a] -> Doc a
- tupled :: [Doc a] -> Doc a
- semiBraces :: [Doc a] -> Doc a
- (<+>) :: Doc a -> Doc a -> Doc a
- (<$>) :: Doc a -> Doc a -> Doc a
- (</>) :: Doc a -> Doc a -> Doc a
- (<$$>) :: Doc a -> Doc a -> Doc a
- (<//>) :: Doc a -> Doc a -> Doc a
- hsep :: [Doc a] -> Doc a
- vsep :: [Doc a] -> Doc a
- fillSep :: [Doc a] -> Doc a
- sep :: [Doc a] -> Doc a
- hcat :: [Doc a] -> Doc a
- vcat :: [Doc a] -> Doc a
- fillCat :: [Doc a] -> Doc a
- cat :: [Doc a] -> Doc a
- punctuate :: Doc a -> [Doc a] -> [Doc a]
- fill :: Int -> Doc a -> Doc a
- fillBreak :: Int -> Doc a -> Doc a
- enclose :: Doc a -> Doc a -> Doc a -> Doc a
- squotes :: Doc a -> Doc a
- dquotes :: Doc a -> Doc a
- parens :: Doc a -> Doc a
- angles :: Doc a -> Doc a
- braces :: Doc a -> Doc a
- brackets :: Doc a -> Doc a
- lparen :: Doc a
- rparen :: Doc a
- langle :: Doc a
- rangle :: Doc a
- lbrace :: Doc a
- rbrace :: Doc a
- lbracket :: Doc a
- rbracket :: Doc a
- squote :: Doc a
- dquote :: Doc a
- semi :: Doc a
- colon :: Doc a
- comma :: Doc a
- space :: Doc a
- dot :: Doc a
- backslash :: Doc a
- equals :: Doc a
- pipe :: Doc a
- string :: String -> Doc a
- int :: Int -> Doc a
- integer :: Integer -> Doc a
- float :: Float -> Doc a
- double :: Double -> Doc a
- rational :: Rational -> Doc a
- bool :: Bool -> Doc a
- annotate :: a -> Doc a -> Doc a
- noAnnotate :: Doc a -> Doc a
- data SimpleDoc a
- renderPretty :: Float -> Int -> Doc a -> SimpleDoc a
- renderCompact :: Doc a -> SimpleDoc a
- displayDecorated :: (a -> String -> String) -> SimpleDoc a -> String
- displayS :: SimpleDoc a -> ShowS
- displayIO :: Handle -> SimpleDoc a -> IO ()
- type SpanList a = [(Int, Int, a)]
- displaySpans :: SimpleDoc a -> (String, SpanList a)
- column :: (Int -> Doc a) -> Doc a
- nesting :: (Int -> Doc a) -> Doc a
- width :: Doc a -> (Int -> Doc a) -> Doc a
Documents, parametrized by their annotations
The abstract data type Doc a represents pretty documents.
Doc a 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
putDoc :: Doc 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 -> Doc 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
The empty document is, indeed, empty. Although empty has no
 content, it does have a 'height' of 1 and behaves exactly like
 (text "") (and is therefore not a unit of <$>).
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.
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 string should be
 used.
(<>) :: Doc a -> Doc a -> Doc aSource
The document (x <> y) concatenates document x and document
 y. It is an associative operation having empty as a left and
 right unit.  (infixr 6)
The line document advances to the next line and indents to the
 current nesting level. Doc aument line behaves like (text " ")
 if the line break is undone by group.
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.
Alignment
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 -> Doc a -> Doc aSource
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 -> Doc a -> Doc aSource
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 :: Doc a -> Doc a -> Doc a -> [Doc a] -> Doc aSource
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 :: [Doc a] -> Doc aSource
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 :: [Doc a] -> Doc aSource
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 :: [Doc a] -> Doc aSource
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
(<+>) :: Doc a -> Doc a -> Doc aSource
The document (x <+> y) concatenates document x and y with a
 space in between.  (infixr 6)
(<$>) :: Doc a -> Doc a -> Doc aSource
The document (x <$> y) concatenates document x and y with a
 line in between. (infixr 5)
(</>) :: Doc a -> Doc a -> Doc aSource
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)
(<$$>) :: Doc a -> Doc a -> Doc aSource
The document (x <$$> y) concatenates document x and y with
 a linebreak in between. (infixr 5)
(<//>) :: Doc a -> Doc a -> Doc aSource
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)
List combinators
hsep :: [Doc a] -> Doc aSource
The document (hsep xs) concatenates all documents xs
 horizontally with (<+>).
vsep :: [Doc a] -> Doc aSource
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 :: [Doc a] -> Doc aSource
The document (fillSep xs) concatenates documents xs
 horizontally with (<+>) as long as its fits the page, than
 inserts a line and continues doing that for all documents in
 xs.
fillSep xs = foldr (\<\/\>) empty xs
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 :: [Doc a] -> Doc aSource
The document (hcat xs) concatenates all documents xs
 horizontally with (<>).
vcat :: [Doc a] -> Doc aSource
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 :: [Doc a] -> Doc aSource
The document (fillCat xs) concatenates documents xs
 horizontally with (<>) as long as its fits the page, than inserts
 a linebreak and continues doing that for all documents in xs.
fillCat xs = foldr (\<\/\/\>) empty xs
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 :: Doc a -> [Doc a] -> [Doc 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 -> Doc a -> Doc aSource
The document (fill i x) renders document x. It than 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  = [("empty","Doc a")
          ,("nest","Int -> Doc a -> Doc 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 empty  :: Doc a
     nest   :: Int -> Doc a -> Doc a
     linebreak :: Doc a
fillBreak :: Int -> Doc a -> Doc aSource
The document (fillBreak i x) first renders document x. It
 than 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 empty  :: Doc a
     nest   :: Int -> Doc a -> Doc a
     linebreak
            :: Doc a
Bracketing combinators
enclose :: Doc a -> Doc a -> Doc a -> Doc aSource
The document (enclose l r x) encloses document x between
 documents l and r using (<>).
enclose l r x = l <> x <> r
brackets :: Doc a -> Doc aSource
Document (brackets x) encloses document x in square brackets,
 "[" and "]".
Character documents
Primitive type documents
string :: String -> Doc aSource
The document (string s) concatenates all characters in s
 using line for newline characters and char for all other
 characters. It is used instead of text whenever the text contains
 newline characters.
rational :: Rational -> Doc aSource
The document (rational r) shows the literal rational r using
 text.
Pretty class
Semantic annotations
noAnnotate :: Doc a -> Doc aSource
Strip annotations from a document. This is useful for re-using the textual formatting of some sub-document, but applying a different high-level annotation.
Rendering
The data type SimpleDoc a 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 a to your own output format.
renderPretty :: Float -> Int -> Doc a -> SimpleDoc aSource
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 :: Doc a -> SimpleDoc aSource
(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.
displayDecorated :: (a -> String -> String) -> SimpleDoc a -> StringSource
Render a string, where annotated regions are decorated by a user-provided function.
displayIO :: Handle -> SimpleDoc a -> IO ()Source
(displayIO handle simpleDoc a) writes simpleDoc a to the file
 handle handle. This function is used for example by 'hPutDoc a':
hPutDoc a handle doc = displayIO handle (renderPretty 0.4 100 doc)
displaySpans :: SimpleDoc a -> (String, SpanList a)Source
Generate a pair of a string and a list of source span/annotation pairs