prettyprinter-1.6.1: A modern, easy to use, well-documented, extensible pretty-printer.

Safe HaskellSafe
LanguageHaskell2010

Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Contents

Description

Conversion of the linked-list-like SimpleDocStream to a tree-like SimpleDocTree.

Synopsis

Type and conversion

data SimpleDocTree ann Source #

A SimpleDocStream is a linked list of different annotated cons cells (SText and then some further SimpleDocStream, SLine and then some further SimpleDocStream, …). This format is very suitable as a target for a layout engine, but not very useful for rendering to a structured format such as HTML, where we don’t want to do a lookahead until the end of some markup. These formats benefit from a tree-like structure that explicitly marks its contents as annotated. SimpleDocTree is that format.

Constructors

STEmpty 
STChar Char 
STText !Int Text

Some layout algorithms use the Since the frequently used length of the Doc, which scales linearly with its length, we cache it in this constructor.

STLine !Int

Int = indentation level for the (next) line

STAnn ann (SimpleDocTree ann)

Annotate the contained document.

STConcat [SimpleDocTree ann]

Horizontal concatenation of multiple documents.

Instances
Functor SimpleDocTree Source #

Alter the document’s annotations.

This instance makes SimpleDocTree more flexible (because it can be used in Functor-polymorphic values), but fmap is much less readable compared to using reAnnotateST in code that only works for SimpleDocTree anyway. Consider using the latter when the type does not matter.

Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Methods

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

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

Foldable SimpleDocTree Source #

Collect all annotations from a document.

Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Methods

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

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

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

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

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

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

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

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

toList :: SimpleDocTree a -> [a] #

null :: SimpleDocTree a -> Bool #

length :: SimpleDocTree a -> Int #

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

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

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

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

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

Traversable SimpleDocTree Source #

Transform a document based on its annotations, possibly leveraging Applicative effects.

Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Methods

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

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

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

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

Eq ann => Eq (SimpleDocTree ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Methods

(==) :: SimpleDocTree ann -> SimpleDocTree ann -> Bool #

(/=) :: SimpleDocTree ann -> SimpleDocTree ann -> Bool #

Ord ann => Ord (SimpleDocTree ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Show ann => Show (SimpleDocTree ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Generic (SimpleDocTree ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

Associated Types

type Rep (SimpleDocTree ann) :: Type -> Type #

Methods

from :: SimpleDocTree ann -> Rep (SimpleDocTree ann) x #

to :: Rep (SimpleDocTree ann) x -> SimpleDocTree ann #

type Rep (SimpleDocTree ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Util.SimpleDocTree

treeForm :: SimpleDocStream ann -> SimpleDocTree ann Source #

Convert a SimpleDocStream to its SimpleDocTree representation.

Manipulating annotations

unAnnotateST :: SimpleDocTree ann -> SimpleDocTree xxx Source #

Remove all annotations. unAnnotate for SimpleDocTree.

reAnnotateST :: (ann -> ann') -> SimpleDocTree ann -> SimpleDocTree ann' Source #

Change the annotation of a document. reAnnotate for SimpleDocTree.

alterAnnotationsST :: (ann -> [ann']) -> SimpleDocTree ann -> SimpleDocTree ann' Source #

Change the annotation of a document to a different annotation, or none at all. alterAnnotations for SimpleDocTree.

Note that this is as powerful as alterAnnotations, allowing one annotation to become multiple ones, contrary to alterAnnotationsS, which cannot do this.

Common use case shortcut definitions

renderSimplyDecorated Source #

Arguments

:: Monoid out 
=> (Text -> out)

Render plain Doc

-> (ann -> out -> out)

How to modify an element with an annotation

-> SimpleDocTree ann 
-> out 

Simplest possible tree-based renderer.

For example, here is a document annotated with (), and the behaviour is to surround annotated regions with »>>>« and »<<<«:

>>> let doc = "hello" <+> annotate () "world" <> "!"
>>> let stdoc = treeForm (layoutPretty defaultLayoutOptions doc)
>>> T.putStrLn (renderSimplyDecorated id (\() x -> ">>>" <> x <> "<<<") stdoc)
hello >>>world<<<!

renderSimplyDecoratedA Source #

Arguments

:: (Applicative f, Monoid out) 
=> (Text -> f out)

Render plain Doc

-> (ann -> f out -> f out)

How to modify an element with an annotation

-> SimpleDocTree ann 
-> f out 

Version of renderSimplyDecoratedA that allows for Applicative effects.