| Copyright | (c) Harvard University 2006-2011 (c) Geoffrey Mainland 2011-2012 |
|---|---|
| License | BSD-style |
| Maintainer | mainland@eecs.harvard.edu |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell98 |
Text.PrettyPrint.Mainland
Contents
Description
This module is based on A Prettier Printer by Phil Wadler in /The Fun of Programming/, Jeremy Gibbons and Oege de Moor (eds) http://homepages.inf.ed.ac.uk/wadler/papers/prettier/prettier.pdf
At the time it was originally written I didn't know about Daan Leijen's
pretty printing module based on the same paper. I have since incorporated
many of his improvements. This module is geared towards pretty printing
source code; its main advantages over other libraries are a Pretty class
that handles precedence and the ability to automatically track the source
locations associated with pretty printed values and output appropriate
#line pragmas.
- data Doc
- empty :: Doc
- text :: String -> Doc
- char :: Char -> Doc
- string :: String -> Doc
- fromText :: Text -> Doc
- fromLazyText :: Text -> Doc
- line :: Doc
- nest :: Int -> Doc -> Doc
- srcloc :: Located a => a -> Doc
- column :: (Int -> Doc) -> Doc
- nesting :: (Int -> Doc) -> Doc
- softline :: Doc
- softbreak :: Doc
- group :: Doc -> Doc
- (<>) :: Monoid m => m -> m -> m
- (<|>) :: Doc -> Doc -> Doc
- (<+>) :: Doc -> Doc -> Doc
- (</>) :: Doc -> Doc -> Doc
- (<+/>) :: Doc -> Doc -> Doc
- (<//>) :: Doc -> Doc -> Doc
- backquote :: Doc
- colon :: Doc
- comma :: Doc
- dot :: Doc
- dquote :: Doc
- equals :: Doc
- semi :: Doc
- space :: Doc
- spaces :: Int -> Doc
- squote :: Doc
- star :: Doc
- langle :: Doc
- rangle :: Doc
- lbrace :: Doc
- rbrace :: Doc
- lbracket :: Doc
- rbracket :: Doc
- lparen :: Doc
- rparen :: Doc
- enclose :: Doc -> Doc -> Doc -> Doc
- angles :: Doc -> Doc
- backquotes :: Doc -> Doc
- braces :: Doc -> Doc
- brackets :: Doc -> Doc
- dquotes :: Doc -> Doc
- parens :: Doc -> Doc
- parensIf :: Bool -> Doc -> Doc
- squotes :: Doc -> Doc
- align :: Doc -> Doc
- hang :: Int -> Doc -> Doc
- indent :: Int -> Doc -> Doc
- folddoc :: (Doc -> Doc -> Doc) -> [Doc] -> Doc
- spread :: [Doc] -> Doc
- stack :: [Doc] -> Doc
- cat :: [Doc] -> Doc
- sep :: [Doc] -> Doc
- punctuate :: Doc -> [Doc] -> [Doc]
- commasep :: [Doc] -> Doc
- semisep :: [Doc] -> Doc
- encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc
- tuple :: [Doc] -> Doc
- list :: [Doc] -> Doc
- data RDoc
- render :: Int -> Doc -> RDoc
- renderCompact :: Doc -> RDoc
- displayS :: RDoc -> ShowS
- prettyS :: Int -> Doc -> ShowS
- pretty :: Int -> Doc -> String
- displayPragmaS :: RDoc -> ShowS
- prettyPragmaS :: Int -> Doc -> ShowS
- prettyPragma :: Int -> Doc -> String
- displayLazyText :: RDoc -> Text
- prettyLazyText :: Int -> Doc -> Text
- displayPragmaLazyText :: RDoc -> Text
- prettyPragmaLazyText :: Int -> Doc -> Text
- putDoc :: Doc -> IO ()
- hPutDoc :: Handle -> Doc -> IO ()
- class Pretty a where
- faildoc :: Monad m => Doc -> m a
- errordoc :: Doc -> a
The document type
Basic combinators
fromLazyText :: Text -> Doc Source
The document consists of the fromLazyText sText s, which should
not contain any newlines.
nest :: Int -> Doc -> Doc Source
The document renders the document nest i dd with the current
indentation level increased by i.
srcloc :: Located a => a -> Doc Source
The document tags the current line with srcloc x. Only
shown when running locOf xprettyPragma and friends.
column :: (Int -> Doc) -> Doc Source
The document is produced by calling column ff with the current colum.
nesting :: (Int -> Doc) -> Doc Source
The document is produced by calling column ff with the
current nesting level.
The document will flatten group dd to one line if there is
room for it, otherwise the original d.
Operators
(<|>) :: Doc -> Doc -> Doc infixl 3 Source
Provide alternative layouts of the same content. Invariant: both arguments must flatten to the same document.
Character documents
Bracketing combinators
backquotes :: Doc -> Doc Source
The document encloses the aligned document backquotes dd in `...`.
parensIf :: Bool -> Doc -> Doc Source
The document encloses the document parensIf p dd in parenthesis if
p is True, and otherwise yields just d.
Alignment and indentation
The document renders align dd with a nesting level set to the current
column.
hang :: Int -> Doc -> Doc Source
The document renders hang i dd with a nesting level set to the
current column plus i, not including the first line.
indent :: Int -> Doc -> Doc Source
The document renders indent i dd with a nesting level set to the
current column plus i, including the first line.
Combining lists of documents
commasep :: [Doc] -> Doc Source
The document comma-space separates commasep dsds, aligning the
resulting document to the current nesting level.
semisep :: [Doc] -> Doc Source
The document semicolon-space separates semisep dsds, aligning the
resulting document to the current nesting level.
encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc Source
The document separates encloseSep l r p dsds with the punctuation p
and encloses the result using l and r. When wrapped, punctuation appears
at the end of the line. The enclosed portion of the document is aligned one
column to the right of the opening document.
> ws = map text (words "The quick brown fox jumps over the lazy dog") > test = pretty 15 (encloseSep lparen rparen comma ws)
will be layed out as:
(The, quick, brown, fox, jumps, over, the, lazy, dog)
The document separates tuple dsds with commas and encloses them with
parentheses.
The document separates list dsds with commas and encloses them with
brackets.
The rendered document type
A rendered document.
Document rendering
renderCompact :: Doc -> RDoc Source
Render a document without indentation on infinitely long lines. Since no 'pretty' printing is involved, this renderer is fast. The resulting output contains fewer characters.
displayPragmaS :: RDoc -> ShowS Source
Display a rendered document with #line pragmas.
prettyPragmaS :: Int -> Doc -> ShowS Source
Render and display a document with #line pragmas.
prettyPragma :: Int -> Doc -> String Source
Render and convert a document to a String with #line pragmas.
> let loc = Loc (Pos "filename" 3 5 7) (Pos "filename" 5 7 9) > in putStrLn $ prettyPragma 80 $ srcloc loc <> text "foo" </> text "bar" </> text "baz"
will be printed as
foo #line 3 "filename" bar baz
displayLazyText :: RDoc -> Text Source
Display a rendered document as Text. Uses a builder.
displayPragmaLazyText :: RDoc -> Text Source
Display a rendered document with #line pragmas as Text. Uses a builder.
prettyPragmaLazyText :: Int -> Doc -> Text Source
Render and convert a document to Text with #line pragmas. Uses a builder.
Document output
hPutDoc :: Handle -> Doc -> IO () Source
Render a document with a width of 80 and print it to the specified handle.
The Pretty type class for pretty printing
Minimal complete definition
Nothing
Instances