Copyright | (c) 2006-2011 Harvard University (c) 2011-2012 Geoffrey Mainland (c) 2015-2017 Drexel University |
---|---|
License | BSD-style |
Maintainer | mainland@drexel.edu |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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 the ability to
automatically track the source locations associated with pretty printed
values and output appropriate #line pragmas and the use of
Text
for output.
Synopsis
- data Doc
- text :: String -> Doc
- bool :: Bool -> Doc
- char :: Char -> Doc
- string :: String -> Doc
- int :: Int -> Doc
- integer :: Integer -> Doc
- float :: Float -> Doc
- double :: Double -> Doc
- rational :: Rational -> Doc
- strictText :: Text -> Doc
- lazyText :: Text -> Doc
- star :: Doc
- colon :: Doc
- comma :: Doc
- dot :: Doc
- equals :: Doc
- semi :: Doc
- space :: Doc
- spaces :: Int -> Doc
- backquote :: Doc
- squote :: Doc
- dquote :: Doc
- langle :: Doc
- rangle :: Doc
- lbrace :: Doc
- rbrace :: Doc
- lbracket :: Doc
- rbracket :: Doc
- lparen :: Doc
- rparen :: Doc
- empty :: Doc
- srcloc :: Located a => a -> Doc
- line :: Doc
- softline :: Doc
- softbreak :: Doc
- (<|>) :: Doc -> Doc -> Doc
- (<+>) :: Doc -> Doc -> Doc
- (</>) :: Doc -> Doc -> Doc
- (<+/>) :: Doc -> Doc -> Doc
- (<//>) :: Doc -> Doc -> Doc
- group :: Doc -> Doc
- flatten :: Doc -> Doc
- enclose :: Doc -> Doc -> Doc -> Doc
- squotes :: Doc -> Doc
- dquotes :: Doc -> Doc
- angles :: Doc -> Doc
- backquotes :: Doc -> Doc
- braces :: Doc -> Doc
- brackets :: Doc -> Doc
- parens :: Doc -> Doc
- parensIf :: Bool -> 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
- align :: Doc -> Doc
- hang :: Int -> Doc -> Doc
- indent :: Int -> Doc -> Doc
- nest :: Int -> Doc -> Doc
- column :: (Int -> Doc) -> Doc
- nesting :: (Int -> Doc) -> Doc
- width :: Doc -> (Int -> Doc) -> Doc
- fill :: Int -> Doc -> Doc
- fillbreak :: Int -> Doc -> Doc
- faildoc :: MonadFail m => Doc -> m a
- errordoc :: Doc -> a
- data RDoc
- render :: Int -> Doc -> RDoc
- renderCompact :: Doc -> RDoc
- displayS :: RDoc -> ShowS
- prettyS :: Int -> Doc -> ShowS
- pretty :: Int -> Doc -> String
- prettyCompactS :: Doc -> ShowS
- prettyCompact :: 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 ()
- putDocLn :: Doc -> IO ()
- hPutDoc :: Handle -> Doc -> IO ()
- hPutDocLn :: Handle -> Doc -> IO ()
The document type
The abstract type of documents.
Constructing documents
Converting values into documents
strictText :: Text -> Doc Source #
The document
consists of the strictText
sText
s
, which should
not contain any newlines.
Simple documents documents
Basic document combinators
srcloc :: Located a => a -> Doc Source #
The document
tags the current line with srcloc
x
. Only
shown when running locOf
xprettyPragma
and friends.
(<|>) :: Doc -> Doc -> Doc infixl 3 Source #
Provide alternative layouts of the same content. Invariant: both arguments must flatten to the same document.
(<//>) :: Doc -> Doc -> Doc infixr 5 Source #
Concatenates two documents with a softbreak
in between.
The document
will flatten group
dd
to one line if there is
room for it, otherwise the original d
.
Wrapping documents in delimiters
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
.
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)
tuple :: [Doc] -> Doc Source #
The document
separates tuple
dsds
with commas and encloses them with
parentheses.
The document
separates list
dsds
with commas and encloses them with
brackets.
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.
nest :: Int -> Doc -> Doc Source #
The document
renders the document nest
i dd
with the current
indentation level increased by i
.
column :: (Int -> Doc) -> Doc Source #
The document
is produced by calling column
ff
with the current
column.
nesting :: (Int -> Doc) -> Doc Source #
The document
is produced by calling column
ff
with the
current nesting level.
width :: Doc -> (Int -> Doc) -> Doc Source #
The document
is produced by concatenating width
d fd
with the result
of calling f
with the width of the document d
.
fill :: Int -> Doc -> Doc Source #
The document
renders document fill
i dx
, appending
space
s until the width is equal to i
. If the width of d
is already
greater than i
, nothing is appended.
Utilities
faildoc :: MonadFail m => Doc -> m a Source #
Equivalent of fail
, but with a document instead of a string.
The rendered document type
A rendered document.
REmpty | The empty document |
RChar !Char RDoc | A single character |
RString !Int String RDoc |
|
RText Text RDoc | |
RLazyText Text RDoc | |
RPos Pos RDoc | Tag output with source location |
RLine !Int RDoc | A newline with the indentation of the subsequent line. If this is
followed by a |
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.
prettyCompactS :: Doc -> ShowS Source #
Render and display a document compactly.
displayPragmaS :: RDoc -> ShowS Source #
Display a rendered document with #line pragmas.
prettyPragma :: Int -> Doc -> String Source #
Render and convert a document to a Doc
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
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
putDoc :: Doc -> IO () Source #
Render a document with a width of 80 and print it to standard output.
putDocLn :: Doc -> IO () Source #
Render a document with a width of 80 and print it to standard output, followed by a newline.