marxup-3.1.1.0: Markup language preprocessor for Haskell

Safe HaskellNone
LanguageHaskell98

MarXup.PrettyPrint

Synopsis

Documentation

encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc Source #

The document (enclosure 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 enclosure:

list xs = enclosure 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]

enclosure :: TeX -> TeX -> TeX -> [Doc] -> Tex Doc Source #

punctuate :: Doc -> [Doc] -> [Doc] 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.)

sep :: [Doc] -> Doc 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)

fillSep :: [Doc] -> Doc Source #

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

hsep :: [Doc] -> Doc Source #

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

vsep :: [Doc] -> Doc 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

cat :: [Doc] -> Doc 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)

fillCat :: [Doc] -> Doc Source #

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

hcat :: [Doc] -> Doc Source #

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

vcat :: [Doc] -> Doc 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.

foldDoc :: (Doc -> Doc -> Doc) -> [Doc] -> Doc Source #

(<+>) :: Doc -> Doc -> Doc infixr 6 Source #

The document (x <+> y) concatenates document x and y with a space in between. (infixr 6)

(</>) :: Doc -> Doc -> Doc 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)

(<//>) :: Doc -> Doc -> Doc 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)

(<$$$>) :: Doc -> Doc -> Doc infixr 5 Source #

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

(<$$>) :: Doc -> Doc -> Doc infixr 5 Source #

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

softline :: Doc Source #

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

softline = group line

softbreak :: Doc Source #

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

softbreak  = group linebreak

enclose :: Doc -> Doc -> Doc -> Doc Source #

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

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

fillBreak :: Double -> Doc -> Doc Source #

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
    nest   :: Double -> Doc -> Doc
    linebreak
           :: Doc

fill :: Double -> Doc -> Doc Source #

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")
         ,("nest","Double -> Doc -> Doc")
         ,("linebreak","Doc")]

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
    nest   :: Double -> Doc -> Doc
    linebreak :: Doc

width :: Doc -> (Double -> Doc) -> Doc Source #

indent :: Double -> Doc -> Doc 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 !

hang :: Double -> Doc -> Doc 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)

align :: Doc -> Doc 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

line :: Doc 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 :: Doc Source #

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

nest :: Double -> Doc -> Doc 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
!