final-pretty-printer-0.1.0.0: Extensible pretty printing with semantic annotations and proportional fonts

Copyright(c) David Darais David Christiansen and Weixi Ma 2016-2017
LicenseMIT
Maintainerdavid.darais@gmail.com
Stabilityexperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Text.PrettyPrint.Final

Contents

Description

This module is the core of the Final Pretty Printer.

Synopsis

Pretty monads and measurement

class (Ord w, Num w, Monoid fmt, Measure w fmt m, Monad m, MonadReader (PEnv w ann fmt) m, MonadWriter (POut w ann) m, MonadState (PState w fmt) m, Alternative m, Functor m) => MonadPretty w ann fmt m | m -> w, m -> ann, m -> fmt Source #

Pretty printing can be done in any pretty monad.

Pretty monads have an additional law: failure (from Alternative) must undo the writer and state effects. So RWST applied to Maybe is fine, but MaybeT of RWS is not.

Instances

MonadPretty w ann fmt m => MonadPretty w ann fmt (EnvT env m) Source # 

class Measure w fmt m | m -> w, m -> fmt where Source #

Monad m can measure lines formatted by fmt, getting width w.

For example, monospaced pretty printing can be measured in Identity, using an Int character count. For proportional fonts, w will typically be something like Double, and m will be IO to support observing the behavior of a font rendering library.

Minimal complete definition

measure

Methods

measure :: Line w fmt -> m w Source #

Measure a particular line

Instances

Measure Int () Identity Source # 

Methods

measure :: Line Int () -> Identity Int Source #

(Monad m, Measure w fmt m) => Measure w fmt (EnvT env m) Source # 

Methods

measure :: Line w fmt -> EnvT env m w Source #

Atomic documents

text :: MonadPretty w ann fmt m => Text -> m () Source #

Include a Text string in the document.

char :: MonadPretty w ann fmt m => Char -> m () Source #

Include a single character in the document.

space :: MonadPretty w ann fmt m => w -> m () Source #

Include a space of a given width in the document.

Semantic annotations

annotate :: MonadPretty w ann fmt m => ann -> m a -> m a Source #

Add a semantic annotation to a document. These annotations are converted into the output stream's notion of decoration by the renderer.

Grouping, alignment, and newlines

newline :: MonadPretty w ann fmt m => m () Source #

A lie break that respects nesting

hardLine :: MonadPretty w ann fmt m => m () Source #

A line break that ignores nesting

ifFlat :: MonadPretty w ann fmt m => m a -> m a -> m a Source #

Conditionally render documents based on whether grouping is undoing newlines.

grouped :: MonadPretty w ann fmt m => m a -> m a Source #

Group a collection of pretty-printer actions, undoing their newlines if possible. If m is [], grouping has a distributive Hughes-style semantics, and if m is Maybe, then grouping has a Wadler-style left-zero semantics. The identity monad gives no grouping.

align :: MonadPretty w ann fmt m => m a -> m a Source #

Vertically align documents.

nest :: MonadPretty w ann fmt m => w -> m a -> m a Source #

Increase the nesting level to render some argument, which will result in the document being indented following newlines.

expr :: MonadPretty w ann fmt m => m a -> m a Source #

Align and group a subdocument, similar to Wadler's group combinator.

Measuring space

measureText :: MonadPretty w ann fmt m => Text -> m w Source #

Measure a string in the current pretty printing context.

Make sure to measure the text in the same dynamic context where its width is to be used, to make sure the right formatting options are applied.

spaceWidth :: MonadPretty w ann fmt m => m w Source #

Measure the width of a space in the current font

emWidth :: MonadPretty w ann fmt m => m w Source #

Measure the width of a capital M in the current font

Separators

hsep :: MonadPretty w ann fmt m => [m ()] -> m () Source #

Separate a collection of documents with a space character.

vsep :: MonadPretty w ann fmt m => [m ()] -> m () Source #

Separate a collection of documents with newlines.

hvsep :: MonadPretty w ann fmt m => [m ()] -> m () Source #

Separate a collection of documents with a space (if there's room) or a newline if not.

hsepTight :: MonadPretty w ann fmt m => [m ()] -> m () Source #

Separate a collection of documents with no space if they can be on the same line, or with the width of a space character in when they cannot.

hvsepTight :: MonadPretty w ann fmt m => [m ()] -> m () Source #

Separate a collection of documents with no space if they can be on the same line, or with newlines if they cannot.

Helpers for common tasks

collection :: MonadPretty w ann fmt m => m () -> m () -> m () -> [m ()] -> m () Source #

Print a collection in comma-initial form.

For sub-documents d1, d2, d3, flat mode is:

[d1, d2, d3]

and multi-line mode is:

[ d1
, d2
, d3
]

Auxiliary datatypes

data PState w fmt Source #

The current state of the pretty printer consists of the line under consideration.

Constructors

PState 

Fields

Instances

(Eq fmt, Eq w) => Eq (PState w fmt) Source # 

Methods

(==) :: PState w fmt -> PState w fmt -> Bool #

(/=) :: PState w fmt -> PState w fmt -> Bool #

(Ord fmt, Ord w) => Ord (PState w fmt) Source # 

Methods

compare :: PState w fmt -> PState w fmt -> Ordering #

(<) :: PState w fmt -> PState w fmt -> Bool #

(<=) :: PState w fmt -> PState w fmt -> Bool #

(>) :: PState w fmt -> PState w fmt -> Bool #

(>=) :: PState w fmt -> PState w fmt -> Bool #

max :: PState w fmt -> PState w fmt -> PState w fmt #

min :: PState w fmt -> PState w fmt -> PState w fmt #

type Line w fmt = [(Chunk w, fmt)] Source #

A current line under consideration for insertion of breaks

data PEnv w ann fmt Source #

The dynamic context of a pretty printing computation

Constructors

PEnv 

Fields

  • maxWidth :: w

    The maximum page width to use

  • maxRibbon :: w

    The maximum amount of non-indentation space to use on one line

  • nesting :: w

    The current indentation level

  • layout :: Layout

    Whether lines are presently being broken or not

  • failure :: Failure

    Whether there is a failure handler waiting to backgrack from laying out a line

  • formatting :: fmt

    A stack of formatting codes to be combined with the monoid op

  • formatAnn :: ann -> fmt

    A means of formatting annotations during rendering. This provides an opportunity for annotations to affect aspects of the output, like font selection, that can have an impact on the width. If this does not agree with the formatting chosen in the final display, then odd things might happen, so the same information should be used here if possible.

localMaxWidth :: MonadReader (PEnv w ann fmt) m => (w -> w) -> m a -> m a Source #

Locally change the maximum horizontal space

data Failure Source #

Is there a failure handler to allow backtracking from the current line?

Constructors

CanFail 
CantFail 

data Layout Source #

Is the pretty printer attempting to put things on one long line?

Constructors

Flat 
Break 

Instances

data Chunk w Source #

Strings or horizontal space to be displayed

Constructors

CText Text

An atomic string. Should not contain formatting spaces or newlines (semantic/object-level spaces OK, but not newlines)

CSpace w

An amount of horizontal space to insert.

Instances

Eq w => Eq (Chunk w) Source # 

Methods

(==) :: Chunk w -> Chunk w -> Bool #

(/=) :: Chunk w -> Chunk w -> Bool #

Ord w => Ord (Chunk w) Source # 

Methods

compare :: Chunk w -> Chunk w -> Ordering #

(<) :: Chunk w -> Chunk w -> Bool #

(<=) :: Chunk w -> Chunk w -> Bool #

(>) :: Chunk w -> Chunk w -> Bool #

(>=) :: Chunk w -> Chunk w -> Bool #

max :: Chunk w -> Chunk w -> Chunk w #

min :: Chunk w -> Chunk w -> Chunk w #

data Atom w Source #

Atomic pieces of output from the pretty printer

Constructors

AChunk (Chunk w)

Inclusion of chunks

ANewline

Newlines to be displayed

Instances

Eq w => Eq (Atom w) Source # 

Methods

(==) :: Atom w -> Atom w -> Bool #

(/=) :: Atom w -> Atom w -> Bool #

Ord w => Ord (Atom w) Source # 

Methods

compare :: Atom w -> Atom w -> Ordering #

(<) :: Atom w -> Atom w -> Bool #

(<=) :: Atom w -> Atom w -> Bool #

(>) :: Atom w -> Atom w -> Bool #

(>=) :: Atom w -> Atom w -> Bool #

max :: Atom w -> Atom w -> Atom w #

min :: Atom w -> Atom w -> Atom w #

data POut w ann Source #

Pretty printer output represents a single annotated string.

Constructors

PNull

The empty output

PAtom (Atom w)

Atomic output

PAnn ann (POut w ann)

An annotated region of output

PSeq (POut w ann) (POut w ann)

The concatenation of two outputs

Instances

Functor (POut w) Source # 

Methods

fmap :: (a -> b) -> POut w a -> POut w b #

(<$) :: a -> POut w b -> POut w a #

(Eq ann, Eq w) => Eq (POut w ann) Source # 

Methods

(==) :: POut w ann -> POut w ann -> Bool #

(/=) :: POut w ann -> POut w ann -> Bool #

(Ord ann, Ord w) => Ord (POut w ann) Source # 

Methods

compare :: POut w ann -> POut w ann -> Ordering #

(<) :: POut w ann -> POut w ann -> Bool #

(<=) :: POut w ann -> POut w ann -> Bool #

(>) :: POut w ann -> POut w ann -> Bool #

(>=) :: POut w ann -> POut w ann -> Bool #

max :: POut w ann -> POut w ann -> POut w ann #

min :: POut w ann -> POut w ann -> POut w ann #

Monoid (POut w ann) Source # 

Methods

mempty :: POut w ann #

mappend :: POut w ann -> POut w ann -> POut w ann #

mconcat :: [POut w ann] -> POut w ann #