| 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 |
Text.PrettyPrint.Annotated.HughesPJ
Contents
Description
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.
- 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, 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.
data TextDetails Source
The TextDetails data type
A TextDetails represents a fragment of text that will be output at some point.
Constructors
| 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
Constructors
| AnnotStart | |
| NoAnnot !TextDetails !Int | |
| AnnotEnd a |
Instances
| Functor AnnotDetails Source | |
| Eq a => Eq (AnnotDetails a) Source | |
| Show a => Show (AnnotDetails a) Source | |
| NFData a => NFData (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
therenest :: 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:
nest0 x = xnestk (nestk' x) =nest(k+k') xnestk (x<>y) =nestk z<>nestk ynestk (x$$y) =nestk x$$nestk ynestkempty=emptyx, if<>nestk y = x<>yxnon-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
renderSpans :: Doc ann -> (String, [Span ann]) Source
Constructors
| Span | |
Fields
| |
Arguments
| :: (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.
Arguments
| :: 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.
Constructors
| Style | |
Fields
| |
renderStyle :: Style -> Doc a -> String Source
Render the Doc to a String using the given Style.
Rendering mode.
Constructors
| PageMode | Normal |
| ZigZagMode | With zig-zag cuts |
| LeftMode | No indentation, infinitely long lines |
| OneLineMode | All on one line |
General rendering
Arguments
| :: 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.
Arguments
| :: 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 |