Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
A re-export of the prettyprinting library, along with some convenience functions.
Synopsis
- hPutDocLn :: Handle -> Doc -> IO ()
- hPutDoc :: Handle -> Doc -> IO ()
- putDocLn :: Doc -> IO ()
- putDoc :: Doc -> IO ()
- prettyPragmaLazyText :: Int -> Doc -> Text
- displayPragmaLazyText :: RDoc -> Text
- prettyLazyText :: Int -> Doc -> Text
- displayLazyText :: RDoc -> Text
- prettyPragma :: Int -> Doc -> String
- prettyPragmaS :: Int -> Doc -> ShowS
- displayPragmaS :: RDoc -> ShowS
- prettyCompact :: Doc -> String
- prettyCompactS :: Doc -> ShowS
- prettyS :: Int -> Doc -> ShowS
- displayS :: RDoc -> ShowS
- renderCompact :: Doc -> RDoc
- render :: Int -> Doc -> RDoc
- errordoc :: Doc -> a
- faildoc :: MonadFail m => Doc -> m a
- fillbreak :: Int -> Doc -> Doc
- fill :: Int -> Doc -> Doc
- width :: Doc -> (Int -> Doc) -> Doc
- nesting :: (Int -> Doc) -> Doc
- column :: (Int -> Doc) -> Doc
- nest :: Int -> Doc -> Doc
- indent :: Int -> Doc -> Doc
- hang :: Int -> Doc -> Doc
- align :: Doc -> Doc
- list :: [Doc] -> Doc
- tuple :: [Doc] -> Doc
- enclosesep :: Doc -> Doc -> Doc -> [Doc] -> Doc
- semisep :: [Doc] -> Doc
- commasep :: [Doc] -> Doc
- punctuate :: Doc -> [Doc] -> [Doc]
- sep :: [Doc] -> Doc
- cat :: [Doc] -> Doc
- stack :: [Doc] -> Doc
- spread :: [Doc] -> Doc
- folddoc :: (Doc -> Doc -> Doc) -> [Doc] -> Doc
- parensIf :: Bool -> Doc -> Doc
- parens :: Doc -> Doc
- brackets :: Doc -> Doc
- braces :: Doc -> Doc
- backquotes :: Doc -> Doc
- angles :: Doc -> Doc
- dquotes :: Doc -> Doc
- squotes :: Doc -> Doc
- enclose :: Doc -> Doc -> Doc -> Doc
- flatten :: Doc -> Doc
- group :: Doc -> Doc
- (<|>) :: Doc -> Doc -> Doc
- (<//>) :: Doc -> Doc -> Doc
- (<+/>) :: Doc -> Doc -> Doc
- (</>) :: Doc -> Doc -> Doc
- (<+>) :: Doc -> Doc -> Doc
- softbreak :: Doc
- softline :: Doc
- line :: Doc
- srcloc :: Located a => a -> Doc
- empty :: Doc
- rparen :: Doc
- lparen :: Doc
- rbracket :: Doc
- lbracket :: Doc
- rbrace :: Doc
- lbrace :: Doc
- rangle :: Doc
- langle :: Doc
- dquote :: Doc
- squote :: Doc
- backquote :: Doc
- spaces :: Int -> Doc
- space :: Doc
- semi :: Doc
- equals :: Doc
- dot :: Doc
- comma :: Doc
- colon :: Doc
- star :: Doc
- lazyText :: Text -> Doc
- strictText :: Text -> Doc
- rational :: Rational -> Doc
- double :: Double -> Doc
- float :: Float -> Doc
- integer :: Integer -> Doc
- int :: Int -> Doc
- string :: String -> Doc
- char :: Char -> Doc
- bool :: Bool -> Doc
- text :: String -> Doc
- data Doc
- data RDoc
- module Text.PrettyPrint.Mainland.Class
- pretty :: Pretty a => a -> String
- prettyDoc :: Int -> Doc -> String
- prettyTuple :: Pretty a => [a] -> String
- prettyText :: Pretty a => a -> Text
- prettyOneLine :: Pretty a => a -> String
- apply :: [Doc] -> Doc
- oneLine :: Doc -> Doc
- annot :: [Doc] -> Doc -> Doc
- nestedBlock :: String -> String -> Doc -> Doc
- textwrap :: String -> Doc
- shorten :: Pretty a => a -> Doc
Documentation
hPutDocLn :: Handle -> Doc -> IO () #
Render a document with a width of 80 and print it to the specified handle, followed by a newline.
hPutDoc :: Handle -> Doc -> IO () #
Render a document with a width of 80 and print it to the specified handle.
Render a document with a width of 80 and print it to standard output, followed by a newline.
prettyPragmaLazyText :: Int -> Doc -> Text #
Render and convert a document to Text
with #line pragmas. Uses a builder.
displayPragmaLazyText :: RDoc -> Text #
Display a rendered document with #line pragmas as Text
. Uses a builder.
displayLazyText :: RDoc -> Text #
Display a rendered document as Text
. Uses a builder.
prettyPragma :: Int -> Doc -> String #
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
prettyPragmaS :: Int -> Doc -> ShowS #
Render and display a document with #line pragmas.
displayPragmaS :: RDoc -> ShowS #
Display a rendered document with #line pragmas.
prettyCompact :: Doc -> String #
Render and convert a document to a String
compactly.
prettyCompactS :: Doc -> ShowS #
Render and display a document compactly.
renderCompact :: Doc -> RDoc #
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.
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.
width :: Doc -> (Int -> Doc) -> Doc #
The document
is produced by concatenating width
d fd
with the result
of calling f
with the width of the document d
.
nesting :: (Int -> Doc) -> Doc #
The document
is produced by calling column
ff
with the
current nesting level.
column :: (Int -> Doc) -> Doc #
The document
is produced by calling column
ff
with the current
column.
The document
renders the document nest
i dd
with the current
indentation level increased by i
.
The document
renders indent
i dd
with a nesting level set to the
current column plus i
, including the first line.
The document
renders hang
i dd
with a nesting level set to the
current column plus i
, not including the first line.
The document
separates list
dsds
with commas and encloses them with
brackets.
The document
separates tuple
dsds
with commas and encloses them with
parentheses.
enclosesep :: Doc -> Doc -> Doc -> [Doc] -> Doc #
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
semicolon-space separates semisep
dsds
, aligning the
resulting document to the current nesting level.
The document
comma-space separates commasep
dsds
, aligning the
resulting document to the current nesting level.
parensIf :: Bool -> Doc -> Doc #
The document
encloses the document parensIf
p dd
in parenthesis if
p
is True
, and otherwise yields just d
.
backquotes :: Doc -> Doc #
The document
encloses the aligned document backquotes
dd
in `...`.
The document
will flatten group
dd
to one line if there is
room for it, otherwise the original d
.
(<|>) :: Doc -> Doc -> Doc infixl 3 #
Provide alternative layouts of the same content. Invariant: both arguments must flatten to the same document.
srcloc :: Located a => a -> Doc #
The document
tags the current line with srcloc
x
. Only
shown when running locOf
xprettyPragma
and friends.
strictText :: Text -> Doc #
The document
consists of the strictText
sText
s
, which should
not contain any newlines.
The abstract type of documents.
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 |
prettyTuple :: Pretty a => [a] -> String Source #
Prettyprint a list enclosed in curly braces.
prettyText :: Pretty a => a -> Text Source #
Prettyprint a value to a Text
, wrapped to 80 characters.
prettyOneLine :: Pretty a => a -> String Source #
Prettyprint a value without any width restriction.
apply :: [Doc] -> Doc Source #
The document
separates apply
dsds
with commas and encloses them with
parentheses.
nestedBlock :: String -> String -> Doc -> Doc Source #
Surround the given document with enclosers and add linebreaks and indents.