Copyright | (c) Trevor Elliott <revor@galois.com> 2015 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | David Terei <code@davidterei.com> |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
This module provides a version of pretty that allows for annotations to be attached to documents. Annotations are arbitrary pieces of metadata that can be attached to sub-documents.
Synopsis
- data Doc a
- data TextDetails
- data AnnotDetails a
- = AnnotStart
- | NoAnnot !TextDetails !Int
- | AnnotEnd a
- char :: Char -> Doc a
- text :: String -> Doc a
- ptext :: String -> Doc a
- sizedText :: Int -> String -> Doc a
- zeroWidthText :: String -> Doc a
- int :: Int -> Doc a
- integer :: Integer -> Doc a
- float :: Float -> Doc a
- double :: Double -> Doc a
- rational :: Rational -> Doc a
- semi :: Doc a
- comma :: Doc a
- colon :: Doc a
- space :: Doc a
- equals :: Doc a
- lparen :: Doc a
- rparen :: Doc a
- lbrack :: Doc a
- rbrack :: Doc a
- lbrace :: Doc a
- rbrace :: Doc a
- parens :: Doc a -> Doc a
- brackets :: Doc a -> Doc a
- braces :: Doc a -> Doc a
- quotes :: Doc a -> Doc a
- doubleQuotes :: Doc a -> Doc a
- maybeParens :: Bool -> Doc a -> Doc a
- maybeBrackets :: Bool -> Doc a -> Doc a
- maybeBraces :: Bool -> Doc a -> Doc a
- maybeQuotes :: Bool -> Doc a -> Doc a
- maybeDoubleQuotes :: Bool -> Doc a -> Doc a
- empty :: Doc a
- (<>) :: Doc a -> Doc a -> Doc a
- (<+>) :: Doc a -> Doc a -> Doc a
- hcat :: [Doc a] -> Doc a
- hsep :: [Doc a] -> Doc a
- ($$) :: Doc a -> Doc a -> Doc a
- ($+$) :: Doc a -> Doc a -> Doc a
- vcat :: [Doc a] -> Doc a
- sep :: [Doc a] -> Doc a
- cat :: [Doc a] -> Doc a
- fsep :: [Doc a] -> Doc a
- fcat :: [Doc a] -> Doc a
- nest :: Int -> Doc a -> Doc a
- hang :: Doc a -> Int -> Doc a -> Doc a
- punctuate :: Doc a -> [Doc a] -> [Doc a]
- annotate :: a -> Doc a -> Doc a
- isEmpty :: Doc a -> Bool
- first :: Doc a -> Doc a -> Doc a
- reduceDoc :: Doc a -> RDoc a
- render :: Doc a -> String
- renderSpans :: Doc ann -> (String, [Span ann])
- data Span a = Span {
- spanStart :: !Int
- spanLength :: !Int
- spanAnnotation :: a
- renderDecorated :: (ann -> String) -> (ann -> String) -> Doc ann -> String
- renderDecoratedM :: Monad m => (ann -> m r) -> (ann -> m r) -> (String -> m r) -> m r -> Doc ann -> m r
- data Style = Style {
- mode :: Mode
- lineLength :: Int
- ribbonsPerLine :: Float
- style :: Style
- renderStyle :: Style -> Doc a -> String
- data Mode
- fullRender :: Mode -> Int -> Float -> (TextDetails -> a -> a) -> a -> Doc b -> a
- fullRenderAnn :: Mode -> Int -> Float -> (AnnotDetails b -> a -> a) -> a -> Doc b -> a
The document type
The abstract type of documents. A Doc represents a set of layouts. A Doc with no occurrences of Union or NoDoc represents just one layout.
Instances
data TextDetails Source #
A TextDetails represents a fragment of text that will be output at some
point in a Doc
.
Chr !Char | A single Char fragment |
Str String | A whole String fragment |
PStr String | Used to represent a Fast String fragment but now deprecated and identical to the Str constructor. |
Instances
data AnnotDetails a Source #
An annotation (side-metadata) attached at a particular point in a Doc
.
Allows carrying non-pretty-printed data around in a Doc
that is attached
at particular points in the structure. Once the Doc
is render to an output
type (such as String
), we can also retrieve where in the rendered document
our annotations start and end (see Span
and renderSpans
).
Instances
Functor AnnotDetails # | |
Defined in Text.PrettyPrint.Annotated.HughesPJ fmap :: (a -> b) -> AnnotDetails a -> AnnotDetails b Source # (<$) :: a -> AnnotDetails b -> AnnotDetails a Source # | |
Eq a => Eq (AnnotDetails a) # | |
Defined in Text.PrettyPrint.Annotated.HughesPJ (==) :: AnnotDetails a -> AnnotDetails a -> Bool Source # (/=) :: AnnotDetails a -> AnnotDetails a -> Bool Source # | |
Show a => Show (AnnotDetails a) # | |
Defined in Text.PrettyPrint.Annotated.HughesPJ | |
NFData a => NFData (AnnotDetails a) # | |
Defined in Text.PrettyPrint.Annotated.HughesPJ rnf :: AnnotDetails a -> () Source # |
Constructing documents
Converting values into documents
sizedText :: Int -> String -> Doc a Source #
Some text with any width. (text s = sizedText (length s) s
)
zeroWidthText :: String -> Doc a Source #
Some text, but without any width. Use for non-printing text such as a HTML or Latex tags
Simple derived documents
Wrapping documents in delimiters
maybeDoubleQuotes :: Bool -> Doc a -> Doc a Source #
Apply doubleQuotes
to Doc
if boolean is true.
Combining documents
($$) :: Doc a -> Doc a -> Doc a infixl 5 Source #
Above, except that if the last line of the first argument stops at least one position before the first line of the second begins, these two lines are overlapped. For example:
text "hi" $$ nest 5 (text "there")
lays out as
hi there
rather than
hi there
nest :: Int -> Doc a -> Doc a Source #
Nest (or indent) a document by a given number of positions
(which may also be negative). nest
satisfies the laws:
nest
0 x = xnest
k (nest
k' x) =nest
(k+k') xnest
k (x<>
y) =nest
k z<>
nest
k ynest
k (x$$
y) =nest
k x$$
nest
k ynest
kempty
=empty
x
, if<>
nest
k y = x<>
yx
non-empty
The side condition on the last law is needed because
empty
is a left identity for <>
.
punctuate :: Doc a -> [Doc a] -> [Doc a] Source #
punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
Annotating documents
Predicates on documents
Utility functions for documents
first :: Doc a -> Doc a -> Doc a Source #
first
returns its first argument if it is non-empty, otherwise its
second.
Rendering documents
Default rendering
Annotation rendering
A Span
represents the result of an annotation after a Doc
has been
rendered, capturing where the annotation now starts and ends in the rendered
output.
Span | |
|
:: (ann -> String) | Starting an annotation. |
-> (ann -> String) | Ending an annotation. |
-> Doc ann | |
-> String |
Render out a String, interpreting the annotations as part of the resulting document.
IMPORTANT: the size of the annotation string does NOT figure into the layout of the document, so the document will lay out as though the annotations are not present.
:: Monad m | |
=> (ann -> m r) | Starting an annotation. |
-> (ann -> m r) | Ending an annotation. |
-> (String -> m r) | Text formatting. |
-> m r | Document end. |
-> Doc ann | |
-> m r |
Render a document with annotations, by interpreting the start and end of the annotations, as well as the text details in the context of a monad.
Rendering with a particular style
A rendering style. Allows us to specify constraints to choose among the many different rendering options.
Style | |
|
Instances
Eq Style # | |
Show Style # | |
Generic Style # | |
type Rep Style # | |
Defined in Text.PrettyPrint.Annotated.HughesPJ type Rep Style = D1 ('MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) (S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mode) :*: (S1 ('MetaSel ('Just "lineLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ribbonsPerLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))) |
Rendering mode.
PageMode | Normal rendering ( |
ZigZagMode | With zig-zag cuts. |
LeftMode | No indentation, infinitely long lines ( |
OneLineMode | All on one line, |
Instances
Eq Mode # | |
Show Mode # | |
Generic Mode # | |
type Rep Mode # | |
Defined in Text.PrettyPrint.Annotated.HughesPJ type Rep Mode = D1 ('MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" 'False) ((C1 ('MetaCons "PageMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZigZagMode" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LeftMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OneLineMode" 'PrefixI 'False) (U1 :: Type -> Type))) |
General rendering
:: Mode | Rendering mode. |
-> Int | Line length. |
-> Float | Ribbons per line. |
-> (TextDetails -> a -> a) | What to do with text. |
-> a | What to do at the end. |
-> Doc b | The document. |
-> a | Result. |
The general rendering interface. Please refer to the Style
and Mode
types for a description of rendering mode, line length and ribbons.
:: Mode | Rendering mode. |
-> Int | Line length. |
-> Float | Ribbons per line. |
-> (AnnotDetails b -> a -> a) | What to do with text. |
-> a | What to do at the end. |
-> Doc b | The document. |
-> a | Result. |
The general rendering interface, supporting annotations. Please refer to
the Style
and Mode
types for a description of rendering mode, line
length and ribbons.