Copyright | (c) David Darais David Christiansen and Weixi Ma 2016-2017 |
---|---|
License | MIT |
Maintainer | david.darais@gmail.com |
Stability | experimental |
Portability | Portable |
Safe Haskell | None |
Language | Haskell2010 |
This module is the core of the Final Pretty Printer.
- 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
- class Measure w fmt m | m -> w, m -> fmt where
- text :: MonadPretty w ann fmt m => Text -> m ()
- char :: MonadPretty w ann fmt m => Char -> m ()
- space :: MonadPretty w ann fmt m => w -> m ()
- annotate :: MonadPretty w ann fmt m => ann -> m a -> m a
- newline :: MonadPretty w ann fmt m => m ()
- hardLine :: MonadPretty w ann fmt m => m ()
- ifFlat :: MonadPretty w ann fmt m => m a -> m a -> m a
- grouped :: MonadPretty w ann fmt m => m a -> m a
- align :: MonadPretty w ann fmt m => m a -> m a
- nest :: MonadPretty w ann fmt m => w -> m a -> m a
- expr :: MonadPretty w ann fmt m => m a -> m a
- measureText :: MonadPretty w ann fmt m => Text -> m w
- spaceWidth :: MonadPretty w ann fmt m => m w
- emWidth :: MonadPretty w ann fmt m => m w
- hsep :: MonadPretty w ann fmt m => [m ()] -> m ()
- vsep :: MonadPretty w ann fmt m => [m ()] -> m ()
- hvsep :: MonadPretty w ann fmt m => [m ()] -> m ()
- hsepTight :: MonadPretty w ann fmt m => [m ()] -> m ()
- hvsepTight :: MonadPretty w ann fmt m => [m ()] -> m ()
- collection :: MonadPretty w ann fmt m => m () -> m () -> m () -> [m ()] -> m ()
- data PState w fmt = PState {}
- type Line w fmt = [(Chunk w, fmt)]
- data PEnv w ann fmt = PEnv {}
- localMaxWidth :: MonadReader (PEnv w ann fmt) m => (w -> w) -> m a -> m a
- data Failure
- data Layout
- data Chunk w
- data Atom w
- data POut w ann
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.
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.
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
The current state of the pretty printer consists of the line under consideration.
type Line w fmt = [(Chunk w, fmt)] Source #
A current line under consideration for insertion of breaks
The dynamic context of a pretty printing computation
PEnv | |
|
localMaxWidth :: MonadReader (PEnv w ann fmt) m => (w -> w) -> m a -> m a Source #
Locally change the maximum horizontal space
Is there a failure handler to allow backtracking from the current line?
Is the pretty printer attempting to put things on one long line?
Strings or horizontal space to be displayed
Atomic pieces of output from the pretty printer