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.
This module should be used as opposed to the
HughesPJ
module. Both are equivalent though as
this module simply re-exports the other.
- data Doc 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
- 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
- render :: Doc a -> String
- renderSpans :: Doc ann -> (String, [Span ann])
- data Span a = Span {
- spanStart, spanLength :: !Int
- spanAnnotation :: a
- data Style = Style {
- mode :: Mode
- lineLength :: Int
- ribbonsPerLine :: Float
- style :: Style
- renderStyle :: Style -> Doc a -> String
- fullRender :: Mode -> Int -> Float -> (TextDetails -> a -> a) -> a -> Doc b -> a
- fullRenderAnn :: Mode -> Int -> Float -> (AnnotDetails b -> a -> a) -> a -> Doc b -> a
- data Mode
- data TextDetails
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.
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
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
Rendering documents
Default rendering
Annotation rendering
renderSpans :: Doc ann -> (String, [Span ann]) Source
Span | |
|
Rendering with a particular style
A rendering style.
Style | |
|
Eq Style | |
Show Style | |
Generic Style | |
type Rep Style = D1 (MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.2" False) (C1 (MetaCons "Style" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mode)) ((:*:) (S1 (MetaSel (Just Symbol "lineLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "ribbonsPerLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))))) |
renderStyle :: Style -> Doc a -> String Source
Render the Doc
to a String using the given Style
.
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.
:: 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 |
Rendering mode.
PageMode | Normal |
ZigZagMode | With zig-zag cuts |
LeftMode | No indentation, infinitely long lines |
OneLineMode | All on one line |
Eq Mode | |
Show Mode | |
Generic Mode | |
type Rep Mode = D1 (MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.2" False) ((:+:) ((:+:) (C1 (MetaCons "PageMode" PrefixI False) U1) (C1 (MetaCons "ZigZagMode" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LeftMode" PrefixI False) U1) (C1 (MetaCons "OneLineMode" PrefixI False) U1))) |
data TextDetails Source
The TextDetails data type
A TextDetails represents a fragment of text that will be output at some point.
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. |
Eq TextDetails | |
Show TextDetails | |
Generic TextDetails | |
NFData TextDetails | |
type Rep TextDetails = D1 (MetaData "TextDetails" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.2" False) ((:+:) (C1 (MetaCons "Chr" PrefixI False) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedUnpack) (Rec0 Char))) ((:+:) (C1 (MetaCons "Str" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) (C1 (MetaCons "PStr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) |