tpdb-1.1.1: Data Type for Rewriting Systems

Safe HaskellSafe-Inferred
LanguageHaskell98

TPDB.Pretty

Synopsis

Documentation

data Doc :: *

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
  

data SimpleDoc :: *

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

renderCompact :: Doc -> SimpleDoc

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

displayIO :: Handle -> SimpleDoc -> IO ()

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

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

class Pretty a where

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

Minimal complete definition

pretty

Methods

pretty :: a -> Doc

prettyList :: [a] -> Doc

Instances

Pretty Bool 
Pretty Char 
Pretty Double 
Pretty Float 
Pretty Int 
Pretty Integer 
Pretty () 
Pretty Text 
Pretty Doc 
Pretty Identifier 
Pretty a => Pretty [a] 
Pretty a => Pretty (Maybe a) 
PrettyTerm a => Pretty (Rule a) 
Pretty a => Pretty (Marked a) 
(Pretty a, Pretty b) => Pretty (Either a b) 
(Pretty a, Pretty b) => Pretty (a, b) 
(Pretty v, Pretty s) => Pretty (Term v s) 
(Pretty s, Pretty r) => Pretty (Problem s r) 
(Pretty s, PrettyTerm r) => Pretty (RS s r) 
(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 
(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) 

fsep :: [Doc] -> Doc Source

hsep :: [Doc] -> Doc

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

vsep :: [Doc] -> Doc

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 laid 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
  

vcat :: [Doc] -> Doc Source

hcat :: [Doc] -> Doc

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

parens :: Doc -> Doc

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

brackets :: Doc -> Doc

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

angles :: Doc -> Doc

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

braces :: Doc -> Doc

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

enclose :: Doc -> Doc -> Doc -> Doc

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

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

punctuate :: Doc -> [Doc] -> [Doc]

(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 laid out on a page width of 20 as:

  (words,in,a,tuple)
  

But when the page width is 15, it is laid 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.)

comma :: Doc

The document comma contains a comma, ",".

nest :: Int -> Doc -> Doc

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
  !
  

empty :: Doc

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

(<>) :: Doc -> Doc -> Doc infixr 6

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)

($$) :: Doc -> Doc -> Doc Source