doclayout-0.5: 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-Inferred
LanguageHaskell2010

Text.DocLayout

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 #

Synonym for renderPlain.

renderPlain :: HasChars a => Maybe Int -> Doc a -> a Source #

Render a Doc without using ANSI escapes. renderPlain (Just n) will use a line length of n to reflow text on breakable spaces. renderPlain Nothing will not reflow text.

renderANSI :: HasChars a => Maybe Int -> Doc a -> Text Source #

Render a Doc with ANSI escapes. renderANSI (Just n) will use a line length of n to reflow text on breakable spaces. renderANSI 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.

literal :: HasChars a => a -> Doc a Source #

Create a Doc from a stringlike value.

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

A literal string. (Like literal, but restricted to String.)

char :: HasChars 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 :: HasChars a => Doc a -> Doc a Source #

Puts a Doc in curly braces.

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

Puts a Doc in square brackets.

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

Puts a Doc in parentheses.

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

Wraps a Doc in single quotes.

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

Wraps a Doc in double quotes.

bold :: HasChars a => Doc a -> Doc a Source #

Puts a Doc in boldface.

italic :: HasChars a => Doc a -> Doc a Source #

Puts a Doc in italics.

underlined :: HasChars a => Doc a -> Doc a Source #

Underlines a Doc.

strikeout :: HasChars a => Doc a -> Doc a Source #

Puts a line through a Doc.

fg :: HasChars a => Color -> Doc a -> Doc a Source #

Set foreground color.

bg :: HasChars a => Color -> Doc a -> Doc a Source #

Set background color.

type Color = Color8 Source #

link :: HasChars a => Text -> Doc a -> Doc a Source #

Make Doc a hyperlink.

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 :: (IsString a, 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.

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

Returns the column that would be occupied by the last laid out character (assuming no wrapping).

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. Ambiguous characters are treated as width 1.

realLength :: HasChars a => a -> Int Source #

Get real length of string, taking into account combining and double-wide characters. Ambiguous characters are treated as width 1.

realLengthNarrowContext :: HasChars a => a -> Int Source #

Get the real length of a string, taking into account combining and double-wide characters. Ambiguous characters are treated as width 1.

realLengthWideContext :: HasChars a => a -> Int Source #

Get the real length of a string, taking into account combining and double-wide characters. Ambiguous characters are treated as width 2.

realLengthNarrowContextNoShortcut :: HasChars a => a -> Int Source #

Like realLengthNarrowContext, but avoids optimizations (shortcuts). This is exposed for testing, to ensure that the optimizations are safe.

realLengthWideContextNoShortcut :: HasChars a => a -> Int Source #

Like realLengthWideContext, but avoids optimizations (shortcuts). This is exposed for testing, to ensure that the optimizations are safe.

Char properties

isSkinToneModifier :: Char -> Bool Source #

Checks whether a character is a skin tone modifier.

isEmojiVariation :: Char -> Bool Source #

Checks whether a character is an emoji variation modifier.

isZWJ :: Char -> Bool Source #

Checks whether a character is a zero-width joiner.

Utility functions

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

Deprecated: unfoldD will be removed from the API.

Unfold a Doc into a flat list.

Types

data Doc a Source #

Document, including structure relevant for layout.

Constructors

Text Int a

Text with specified width.

Block Int [Attributed 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.

CookedText Int (Attributed a)

Text which doesn't need further cooking

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.

Styled StyleReq (Doc a) 
Linked Text (Doc a)

A hyperlink

Empty 

Instances

Instances details
Foldable Doc Source # 
Instance details

Defined in Text.DocLayout

Methods

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

foldMap :: Monoid m => (a -> m) -> Doc a -> 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) #

Functor Doc Source # 
Instance details

Defined in Text.DocLayout

Methods

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

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

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

Defined in Text.DocLayout

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Doc a -> c (Doc a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Doc a) #

toConstr :: Doc a -> Constr #

dataTypeOf :: Doc a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Doc a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Doc a)) #

gmapT :: (forall b. Data b => b -> b) -> Doc a -> Doc a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Doc a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Doc a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Doc a -> m (Doc a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc a -> m (Doc a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc a -> m (Doc a) #

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

Defined in Text.DocLayout

Methods

fromString :: String -> 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 #

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 #

Generic (Doc a) Source # 
Instance details

Defined in Text.DocLayout

Associated Types

type Rep (Doc a) :: Type -> Type #

Methods

from :: Doc a -> Rep (Doc a) x #

to :: Rep (Doc a) x -> Doc a #

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

Defined in Text.DocLayout

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 #

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

Defined in Text.DocLayout

Methods

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

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

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

Defined in Text.DocLayout

Methods

compare :: Doc a -> Doc a -> Ordering #

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

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

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

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

max :: Doc a -> Doc a -> Doc a #

min :: Doc a -> Doc a -> Doc a #

type Rep (Doc a) Source # 
Instance details

Defined in Text.DocLayout

type Rep (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. Minimal definition is foldrChar and foldlChar, but defining the other methods can give better performance.

Minimal complete definition

foldrChar, foldlChar

Methods

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

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

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

isNull :: a -> Bool Source #

splitLines :: a -> [a] Source #

build :: a -> Builder Source #

Instances

Instances details
HasChars Text Source # 
Instance details

Defined in Text.DocLayout.HasChars

Methods

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

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

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

isNull :: Text -> Bool Source #

splitLines :: Text -> [Text] Source #

build :: Text -> Builder Source #

HasChars Text Source # 
Instance details

Defined in Text.DocLayout.HasChars

Methods

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

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

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

isNull :: Text -> Bool Source #

splitLines :: Text -> [Text] Source #

build :: Text -> Builder Source #

HasChars String Source # 
Instance details

Defined in Text.DocLayout.HasChars

Methods

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

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

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

isNull :: String -> Bool Source #

splitLines :: String -> [String] Source #

build :: String -> Builder Source #

HasChars a => HasChars (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.HasChars

Methods

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

foldlChar :: (b -> Char -> b) -> b -> Attributed a -> b Source #

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

isNull :: Attributed a -> Bool Source #

splitLines :: Attributed a -> [Attributed a] Source #

build :: Attributed a -> Builder Source #

data Attributed a Source #

A sequence of strings with font attributes.

Instances

Instances details
Foldable Attributed Source # 
Instance details

Defined in Text.DocLayout.Attributed

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Attributed a -> m #

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

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

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

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

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

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

toList :: Attributed a -> [a] #

null :: Attributed a -> Bool #

length :: Attributed a -> Int #

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

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

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

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

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

Traversable Attributed Source # 
Instance details

Defined in Text.DocLayout.Attributed

Methods

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

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

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

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

Functor Attributed Source # 
Instance details

Defined in Text.DocLayout.Attributed

Methods

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

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

Data a => Data (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.Attributed

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attributed a -> c (Attributed a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Attributed a) #

toConstr :: Attributed a -> Constr #

dataTypeOf :: Attributed a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Attributed a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Attributed a)) #

gmapT :: (forall b. Data b => b -> b) -> Attributed a -> Attributed a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attributed a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attributed a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Attributed a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Attributed a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attributed a -> m (Attributed a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attributed a -> m (Attributed a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attributed a -> m (Attributed a) #

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

Defined in Text.DocLayout.Attributed

Methods

fromString :: String -> Attributed a #

Monoid a => Monoid (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.Attributed

Semigroup a => Semigroup (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.Attributed

Generic (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.Attributed

Associated Types

type Rep (Attributed a) :: Type -> Type #

Methods

from :: Attributed a -> Rep (Attributed a) x #

to :: Rep (Attributed a) x -> Attributed a #

Read a => Read (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.Attributed

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

Defined in Text.DocLayout.Attributed

HasChars a => HasChars (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.HasChars

Methods

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

foldlChar :: (b -> Char -> b) -> b -> Attributed a -> b Source #

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

isNull :: Attributed a -> Bool Source #

splitLines :: Attributed a -> [Attributed a] Source #

build :: Attributed a -> Builder Source #

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

Defined in Text.DocLayout.Attributed

Methods

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

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

Ord a => Ord (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.Attributed

type Rep (Attributed a) Source # 
Instance details

Defined in Text.DocLayout.Attributed

type Rep (Attributed a)