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

Safe HaskellSafe
LanguageHaskell2010

Data.Text.Prettyprint.Doc.Internal.Type

Description

Internal module with stability guarantees

This module exposes the internals of the Doc type so other libraries can write adaptors to/from it. For all other uses, please use only the API provided by non-internal modules.

Although this module is internal, it follows the usual package versioning policy, AKA Haskell’s version of semantic versioning. In other words, this module is as stable as the public API.

Synopsis

Documentation

data Doc ann Source #

The abstract data type Doc ann represents pretty documents that have been annotated with data of type ann.

More specifically, a value of type Doc represents a non-empty set of possible layouts of a document. The layout functions select one of these possibilities, taking into account things like the width of the output document.

The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as

  • color information (e.g. when rendering to the terminal)
  • mouseover text (e.g. when rendering to rich HTML)
  • whether to show something or not (to allow simple or detailed versions)

The simplest way to display a Doc is via the Show class.

>>> putStrLn (show (vsep ["hello", "world"]))
hello
world

Constructors

Fail

Occurs when flattening a line. The layouter will reject this document, choosing a more suitable rendering.

Empty

The empty document; conceptually the unit of Cat

Char !Char

invariant: not '\n'

Text !Int !Text

Invariants: at least two characters long, does not contain '\n'. For empty documents, there is Empty; for singleton documents, there is Char; newlines should be replaced by e.g. Line.

Since the frequently used length of Doc is O(length), we cache it in this constructor.

Line

Hard line break

FlatAlt (Doc ann) (Doc ann)

Lay out the first Doc, but when flattened (via group), fall back to the second. The flattened version should in general be higher and narrower than the fallback.

Cat (Doc ann) (Doc ann)

Concatenation of two documents

Nest !Int (Doc ann)

Document indented by a number of columns

Union (Doc ann) (Doc ann)

Invariant: The first lines of first document should be longer than the first lines of the second one, so the layout algorithm can pick the one that fits best. Used to implement layout alternatives for group.

Column (Int -> Doc ann)

React on the current cursor position, see column

WithPageWidth (PageWidth -> Doc ann)

React on the document's width, see pageWidth

Nesting (Int -> Doc ann)

React on the current nesting level, see nesting

Annotated ann (Doc ann)

Add an annotation to the enclosed Doc. Can be used for example to add styling directives or alt texts that can then be used by the renderer.

Instances
Functor Doc Source #

Alter the document’s annotations.

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

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

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

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

Show (Doc ann) Source #

(show doc) prettyprints document doc with defaultLayoutOptions, ignoring all annotations.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

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

show :: Doc ann -> String #

showList :: [Doc ann] -> ShowS #

IsString (Doc ann) Source #
>>> pretty ("hello\nworld")
hello
world

This instance uses the Pretty Doc instance, and uses the same newline to line conversion.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

fromString :: String -> Doc ann #

Generic (Doc ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Associated Types

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

Methods

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

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

Semigroup (Doc ann) Source #
x <> y = hcat [x, y]
>>> "hello" <> "world" :: Doc ann
helloworld
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

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

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

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

Monoid (Doc ann) Source #
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

mempty :: Doc ann #

mappend :: Doc ann -> Doc ann -> Doc ann #

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

type Rep (Doc ann) Source # 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

type Rep (Doc ann) = D1 (MetaData "Doc" "Data.Text.Prettyprint.Doc.Internal" "prettyprinter-1.3.0-6qg3eRt5h66FauUzehlm4q" False) (((C1 (MetaCons "Fail" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Empty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char)))) :+: (C1 (MetaCons "Text" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: (C1 (MetaCons "Line" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FlatAlt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)))))) :+: ((C1 (MetaCons "Cat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))) :+: (C1 (MetaCons "Nest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))) :+: C1 (MetaCons "Union" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))))) :+: ((C1 (MetaCons "Column" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 (MetaCons "WithPageWidth" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PageWidth -> Doc ann)))) :+: (C1 (MetaCons "Nesting" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 (MetaCons "Annotated" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ann) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)))))))