doclayout-0.1: A prettyprinting library for laying out text documents.

CopyrightCopyright (C) 2010-2019 John MacFarlane
LicenseBSD 3
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Text.DocLayout

Contents

Description

A prettyprinting library for the production of text documents, including wrapped text, indentation and other prefixes, and blocks for tables.

Synopsis

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

cr :: Doc a Source #

A carriage return. Does nothing if we're at the beginning of a line; otherwise inserts a newline.

blankline :: Doc a Source #

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).

space :: Doc a Source #

A breaking (reflowable) space.

text :: IsString a => String -> Doc a Source #

A literal string.

char :: IsString a => Char -> Doc a Source #

A character.

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).

flush :: Doc a -> Doc a Source #

Makes a Doc flush against the left margin.

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.

nowrap :: IsString a => Doc a -> Doc a Source #

Makes a Doc non-reflowable.

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.

cblock :: HasChars a => Int -> Doc a -> Doc a Source #

Like lblock but aligned centered.

rblock :: HasChars a => Int -> Doc a -> Doc a Source #

Like lblock but aligned to the right.

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.

nestle :: Doc a -> Doc a Source #

Removes leading blank lines from a Doc.

chomp :: Doc a -> Doc a Source #

Chomps trailing blank space off of a Doc.

inside :: Doc a -> Doc a -> Doc a -> Doc a Source #

Encloses a Doc inside a start and end Doc.

braces :: IsString a => Doc a -> Doc a Source #

Puts a Doc in curly braces.

brackets :: IsString a => Doc a -> Doc a Source #

Puts a Doc in square brackets.

parens :: IsString a => Doc a -> Doc a Source #

Puts a Doc in parentheses.

quotes :: IsString a => Doc a -> Doc a Source #

Wraps a Doc in single quotes.

doubleQuotes :: IsString a => Doc a -> Doc a Source #

Wraps a Doc in double quotes.

empty :: Doc a Source #

The empty document.

Functions for concatenating documents

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

Concatenate a list of Docs, putting breakable spaces between them.

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

a $$ b puts a above b.

($+$) :: Doc a -> Doc a -> Doc a infixr 5 Source #

a $+$ b puts a above b, with a blank line between.

hcat :: [Doc a] -> Doc a Source #

Concatenate documents horizontally.

hsep :: [Doc a] -> Doc a Source #

Same as hcat, but putting breakable spaces between the Docs.

vcat :: [Doc a] -> Doc a Source #

List version of $$.

vsep :: [Doc a] -> Doc a Source #

List version of $+$.

Functions for querying documents

isEmpty :: Doc a -> Bool Source #

True if the document is empty.

offset :: HasChars a => Doc a -> Int Source #

Returns the width of a Doc.

minOffset :: HasChars a => Doc a -> Int Source #

Returns the minimal width of a Doc when reflowed at breakable spaces.

height :: HasChars a => Doc a -> Int Source #

Returns the height of a block or other Doc.

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

data Doc a Source #

Document, including structure relevant for layout.

Constructors

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
Functor Doc Source # 
Instance details

Defined in Text.DocLayout

Methods

fmap :: (a -> b) -> Doc a -> Doc b #

(<$) :: a -> Doc b -> Doc a #

Foldable Doc Source # 
Instance details

Defined in Text.DocLayout

Methods

fold :: Monoid m => Doc m -> m #

foldMap :: Monoid m => (a -> m) -> Doc a -> m #

foldr :: (a -> b -> b) -> b -> Doc a -> b #

foldr' :: (a -> b -> b) -> b -> Doc a -> b #

foldl :: (b -> a -> b) -> b -> Doc a -> b #

foldl' :: (b -> a -> b) -> b -> Doc a -> b #

foldr1 :: (a -> a -> a) -> Doc a -> a #

foldl1 :: (a -> a -> a) -> Doc a -> a #

toList :: Doc a -> [a] #

null :: Doc a -> Bool #

length :: Doc a -> Int #

elem :: Eq a => a -> Doc a -> Bool #

maximum :: Ord a => Doc a -> a #

minimum :: Ord a => Doc a -> a #

sum :: Num a => Doc a -> a #

product :: Num a => Doc a -> a #

Traversable Doc Source # 
Instance details

Defined in Text.DocLayout

Methods

traverse :: Applicative f => (a -> f b) -> Doc a -> f (Doc b) #

sequenceA :: Applicative f => Doc (f a) -> f (Doc a) #

mapM :: Monad m => (a -> m b) -> Doc a -> m (Doc b) #

sequence :: Monad m => Doc (m a) -> m (Doc a) #

Eq a => Eq (Doc a) Source # 
Instance details

Defined in Text.DocLayout

Methods

(==) :: Doc a -> Doc a -> Bool #

(/=) :: Doc a -> Doc a -> Bool #

Show a => Show (Doc a) Source # 
Instance details

Defined in Text.DocLayout

Methods

showsPrec :: Int -> Doc a -> ShowS #

show :: Doc a -> String #

showList :: [Doc a] -> ShowS #

IsString a => IsString (Doc a) Source # 
Instance details

Defined in Text.DocLayout

Methods

fromString :: String -> Doc a #

Semigroup (Doc a) Source # 
Instance details

Defined in Text.DocLayout

Methods

(<>) :: Doc a -> Doc a -> Doc a #

sconcat :: NonEmpty (Doc a) -> Doc a #

stimes :: Integral b => b -> Doc a -> Doc a #

Monoid (Doc a) Source # 
Instance details

Defined in Text.DocLayout

Methods

mempty :: Doc a #

mappend :: Doc a -> Doc a -> Doc a #

mconcat :: [Doc a] -> Doc a #

class (IsString a, Semigroup a, Monoid a, Show a) => HasChars a where Source #

Class abstracting over various string types that can fold over characters.

Methods

foldrChar :: (Char -> b -> b) -> b -> a -> b Source #

splitLines :: a -> [a] Source #

replicateChar :: Int -> Char -> a Source #

isNull :: a -> Bool Source #

Instances
HasChars String Source # 
Instance details

Defined in Text.DocLayout

Methods

foldrChar :: (Char -> b -> b) -> b -> String -> b Source #

splitLines :: String -> [String] Source #

replicateChar :: Int -> Char -> String Source #

isNull :: String -> Bool Source #

HasChars Text Source # 
Instance details

Defined in Text.DocLayout

Methods

foldrChar :: (Char -> b -> b) -> b -> Text -> b Source #

splitLines :: Text -> [Text] Source #

replicateChar :: Int -> Char -> Text Source #

isNull :: Text -> Bool Source #

HasChars Text Source # 
Instance details

Defined in Text.DocLayout

Methods

foldrChar :: (Char -> b -> b) -> b -> Text -> b Source #

splitLines :: Text -> [Text] Source #

replicateChar :: Int -> Char -> Text Source #

isNull :: Text -> Bool Source #