symantic-document-1.5.3.20200320: Symantics combinators for generating documents.
Safe HaskellNone
LanguageHaskell2010

Symantic.Document.Plain

Synopsis

Type Plain

newtype Plain d Source #

Church encoded for performance concerns. Kind like ParsecT in megaparsec but a little bit different due to the use of PlainFit for implementing breakingSpace correctly when in the left hand side of (<>). Prepending is done using continuation, like in a difference list.

Constructors

Plain 

Fields

Instances

Instances details
(From (Word Char) d, Spaceable d) => From Char (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: Char -> Plain d Source #

(From (Word String) d, Spaceable d) => From String (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: String -> Plain d Source #

(From (Word Text) d, Spaceable d) => From Text (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: Text -> Plain d Source #

(From (Word Text) d, Spaceable d) => From Text (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: Text -> Plain d Source #

(Show d, Spaceable d) => Show (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

showsPrec :: Int -> Plain d -> ShowS #

show :: Plain d -> String #

showList :: [Plain d] -> ShowS #

(From (Word String) d, Spaceable d) => IsString (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

fromString :: String -> Plain d #

Semigroup d => Semigroup (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

(<>) :: Plain d -> Plain d -> Plain d #

sconcat :: NonEmpty (Plain d) -> Plain d #

stimes :: Integral b => b -> Plain d -> Plain d #

Monoid d => Monoid (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

mempty :: Plain d #

mappend :: Plain d -> Plain d -> Plain d #

mconcat :: [Plain d] -> Plain d #

Spaceable d => Justifiable (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

justify :: Plain d -> Plain d Source #

Spaceable d => Wrappable (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

(Spaceable d, From (Word Char) d, From (Word String) d) => Listable (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

ul :: Traversable f => f (Plain d) -> Plain d Source #

ol :: Traversable f => f (Plain d) -> Plain d Source #

Spaceable d => Indentable (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

align :: Plain d -> Plain d Source #

setIndent :: Plain d -> Indent -> Plain d -> Plain d Source #

incrIndent :: Plain d -> Indent -> Plain d -> Plain d Source #

hang :: Indent -> Plain d -> Plain d Source #

fill :: Width -> Plain d -> Plain d Source #

fillOrBreak :: Width -> Plain d -> Plain d Source #

(Semigroup d, From [SGR] d) => Colorable16 (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

(Semigroup d, From [SGR] d) => Decorable (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

bold :: Plain d -> Plain d Source #

underline :: Plain d -> Plain d Source #

italic :: Plain d -> Plain d Source #

Spaceable d => Spaceable (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

newline :: Plain d Source #

space :: Plain d Source #

spaces :: Column -> Plain d Source #

unlines :: Foldable f => f (Line (Plain d)) -> Plain d Source #

unwords :: (Foldable f, Functor f) => f (Word (Plain d)) -> Plain d Source #

catLines :: (Foldable f, Functor f) => f (Line (Plain d)) -> Plain d Source #

(<+>) :: Plain d -> Plain d -> Plain d Source #

(</>) :: Plain d -> Plain d -> Plain d Source #

catH :: Foldable f => f (Plain d) -> Plain d Source #

catV :: Foldable f => f (Plain d) -> Plain d Source #

(From [SGR] d, Semigroup d) => From [SGR] (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: [SGR] -> Plain d Source #

(From (Word s) d, Semigroup d, Lengthable s) => From (Word s) (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: Word s -> Plain d Source #

(From (Word s) d, Lengthable s, Spaceable d, Splitable s) => From (Line s) (Plain d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: Line s -> Plain d Source #

Type PlainState

data PlainState d Source #

Constructors

PlainState 

Fields

Instances

Instances details
Show d => Show (PlainState d) Source # 
Instance details

Defined in Symantic.Document.Plain

Type PlainInh

Type PlainFit

type PlainFit d = (d -> d) -> (d -> d) -> d Source #

Double continuation to qualify the returned document as fitting or overflowing the given plainInh_width. It's like (Bool,d) in a normal style (a non continuation-passing-style).

Type PlainChunk

data PlainChunk d Source #

Constructors

PlainChunk_Ignored !d

Ignored by the justification but kept in place. Used for instance to put ANSI sequences.

PlainChunk_Word !(Word d) 
PlainChunk_Spaces !Width

spaces preserved to be interleaved correctly with PlainChunk_Ignored.

Instances

Instances details
Show d => Show (PlainChunk d) Source # 
Instance details

Defined in Symantic.Document.Plain

Lengthable d => Lengthable (PlainChunk d) Source # 
Instance details

Defined in Symantic.Document.Plain

From [SGR] d => From [SGR] (PlainChunk d) Source # 
Instance details

Defined in Symantic.Document.Plain

Methods

from :: [SGR] -> PlainChunk d Source #

flushlinePlain :: Spaceable d => Plain d Source #

Commit plainState_buffer upto there, so that it won't be justified.

Justifying

countWordsPlain :: [PlainChunk d] -> Natural Source #

(countWordsPlain ps) returns the number of words in (ps) clearly separated by spaces.

justifyPadding :: Natural -> Natural -> [Natural] Source #

(justifyPadding a b) returns the padding lengths to reach (a) in (b) pads, using the formula: (a == m*(q + q+1) + (r-'m)*(q+1) + (b-r-m)*q) where (q+1) and (q) are the two padding lengths used and (m = min (b-r) r).

A simple implementation of justifyPadding could be: justifyPadding a b = join (replicate m [q,q+1]) <> (replicate (r-m) (q+1) <> (replicate ((b-r)-m) q where (q,r) = adivModb m = min (b-r) r

joinLinePlainChunk :: Monoid d => Spaceable d => [PlainChunk d] -> d Source #

Just concat PlainChunks with no justification.

padLinePlainChunk :: Spaceable d => [PlainChunk d] -> [Width] -> d Source #

Interleave PlainChunks with Widths from justifyPadding.

Escaping

plainSGR :: Semigroup d => From [SGR] d => SGR -> Plain d -> Plain d Source #