Copyright | Copyright (C) 2010-2019 John MacFarlane |
---|---|
License | BSD 3 |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
A prettyprinting library for the production of text documents, including wrapped text, indentation and other prefixes, and blocks for tables.
Synopsis
- render :: HasChars a => Maybe Int -> Doc a -> a
- cr :: Doc a
- blankline :: Doc a
- blanklines :: Int -> Doc a
- space :: Doc a
- literal :: HasChars a => a -> Doc a
- text :: HasChars a => String -> Doc a
- char :: HasChars a => Char -> Doc a
- prefixed :: IsString a => String -> Doc a -> Doc a
- flush :: Doc a -> Doc a
- nest :: IsString a => Int -> Doc a -> Doc a
- hang :: IsString a => Int -> Doc a -> Doc a -> Doc a
- beforeNonBlank :: Doc a -> Doc a
- nowrap :: IsString a => Doc a -> Doc a
- afterBreak :: Text -> Doc a
- lblock :: HasChars a => Int -> Doc a -> Doc a
- cblock :: HasChars a => Int -> Doc a -> Doc a
- rblock :: HasChars a => Int -> Doc a -> Doc a
- vfill :: HasChars a => a -> Doc a
- nestle :: Doc a -> Doc a
- chomp :: Doc a -> Doc a
- inside :: Doc a -> Doc a -> Doc a -> Doc a
- braces :: HasChars a => Doc a -> Doc a
- brackets :: HasChars a => Doc a -> Doc a
- parens :: HasChars a => Doc a -> Doc a
- quotes :: HasChars a => Doc a -> Doc a
- doubleQuotes :: HasChars a => Doc a -> Doc a
- empty :: Doc a
- (<+>) :: Doc a -> Doc a -> Doc a
- ($$) :: Doc a -> Doc a -> Doc a
- ($+$) :: Doc a -> Doc a -> Doc a
- hcat :: [Doc a] -> Doc a
- hsep :: [Doc a] -> Doc a
- vcat :: [Doc a] -> Doc a
- vsep :: [Doc a] -> Doc a
- isEmpty :: Doc a -> Bool
- offset :: (IsString a, HasChars a) => Doc a -> Int
- minOffset :: HasChars a => Doc a -> Int
- updateColumn :: HasChars a => Doc a -> Int -> Int
- height :: HasChars a => Doc a -> Int
- charWidth :: Char -> Int
- realLength :: HasChars a => a -> Int
- data Doc a
- = Text Int a
- | Block Int [a]
- | VFill Int a
- | Prefixed Text (Doc a)
- | BeforeNonBlank (Doc a)
- | Flush (Doc a)
- | BreakingSpace
- | AfterBreak Text
- | CarriageReturn
- | NewLine
- | BlankLines Int
- | Concat (Doc a) (Doc a)
- | Empty
- class (IsString a, Semigroup a, Monoid a, Show a) => HasChars a where
- foldrChar :: (Char -> b -> b) -> b -> a -> b
- foldlChar :: (b -> Char -> b) -> b -> a -> b
- replicateChar :: Int -> Char -> a
- isNull :: a -> Bool
- splitLines :: a -> [a]
Rendering
render :: HasChars a => Maybe Int -> Doc a -> a Source #
Render a Doc
. render (Just n)
will use
a line length of n
to reflow text on breakable spaces.
render Nothing
will not reflow text.
Doc constructors
A carriage return. Does nothing if we're at the beginning of a line; otherwise inserts a newline.
Inserts a blank line unless one exists already.
(blankline <> blankline
has the same effect as blankline
.
blanklines :: Int -> Doc a Source #
Inserts blank lines unless they exist already.
(blanklines m <> blanklines n
has the same effect as blanklines (max m n)
.
text :: HasChars a => String -> Doc a Source #
A literal string. (Like literal
, but restricted to String.)
prefixed :: IsString a => String -> Doc a -> Doc a Source #
Uses the specified string as a prefix for every line of the inside document (except the first, if not at the beginning of the line).
nest :: IsString a => Int -> Doc a -> Doc a Source #
Indents a Doc
by the specified number of spaces.
hang :: IsString a => Int -> Doc a -> Doc a -> Doc a Source #
A hanging indent. hang ind start doc
prints start
,
then doc
, leaving an indent of ind
spaces on every
line but the first.
beforeNonBlank :: Doc a -> Doc a Source #
beforeNonBlank d
conditionally includes d
unless it is
followed by blank space.
afterBreak :: Text -> Doc a Source #
Content to print only if it comes at the beginning of a line,
to be used e.g. for escaping line-initial .
in roff man.
lblock :: HasChars a => Int -> Doc a -> Doc a Source #
lblock n d
is a block of width n
characters, with
text derived from d
and aligned to the left.
vfill :: HasChars a => a -> Doc a Source #
An expandable border that, when placed next to a box, expands to the height of the box. Strings cycle through the list provided.
Functions for concatenating documents
(<+>) :: Doc a -> Doc a -> Doc a infixr 6 Source #
Concatenate a list of Doc
s, putting breakable spaces
between them.
($+$) :: Doc a -> Doc a -> Doc a infixr 5 Source #
a $+$ b
puts a
above b
, with a blank line between.
Functions for querying documents
minOffset :: HasChars a => Doc a -> Int Source #
Returns the minimal width of a Doc
when reflowed at breakable spaces.
updateColumn :: HasChars a => Doc a -> Int -> Int Source #
Returns the column that would be occupied by the last laid out character (assuming no wrapping).
charWidth :: Char -> Int Source #
Returns width of a character in a monospace font: 0 for a combining character, 1 for a regular character, 2 for an East Asian wide character.
realLength :: HasChars a => a -> Int Source #
Get real length of string, taking into account combining and double-wide characters.
Types
Document, including structure relevant for layout.
Text Int a | Text with specified width. |
Block Int [a] | A block with a width and lines. |
VFill Int a | A vertically expandable block; when concatenated with a block, expands to height of block, with each line containing the specified text. |
Prefixed Text (Doc a) | Doc with each line prefixed with text. Note that trailing blanks are omitted from the prefix when the line after it is empty. |
BeforeNonBlank (Doc a) | Doc that renders only before nonblank. |
Flush (Doc a) | Doc laid out flush to left margin. |
BreakingSpace | A space or line break, in context. |
AfterBreak Text | Text printed only at start of line. |
CarriageReturn | Newline unless we're at start of line. |
NewLine | newline. |
BlankLines Int | Ensure a number of blank lines. |
Concat (Doc a) (Doc a) | Two documents concatenated. |
Empty |
Instances
class (IsString a, Semigroup a, Monoid a, Show a) => HasChars a where Source #
Class abstracting over various string types that
can fold over characters. Minimal definition is foldrChar
and foldlChar
, but defining the other methods can give better
performance.
foldrChar :: (Char -> b -> b) -> b -> a -> b Source #
foldlChar :: (b -> Char -> b) -> b -> a -> b Source #
replicateChar :: Int -> Char -> a Source #
splitLines :: a -> [a] Source #