Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains logic for pretty-printing expressions, including support for syntax highlighting
Synopsis
- data Ann
- annToAnsiStyle :: Ann -> AnsiStyle
- prettyExpr :: Pretty a => Expr s a -> Doc Ann
- data CharacterSet
- detectCharacterSet :: Expr Src a -> CharacterSet
- prettyCharacterSet :: Pretty a => CharacterSet -> Expr Src a -> Doc Ann
- layout :: Doc ann -> SimpleDocStream ann
- layoutOpts :: LayoutOptions
- escapeEnvironmentVariable :: Text -> Text
- escapeLabel :: Bool -> Text -> Text
- temporalToText :: Pretty a => Expr s a -> Maybe Text
Pretty
Annotation type used to tag elements in a pretty-printed document for syntax highlighting purposes
annToAnsiStyle :: Ann -> AnsiStyle Source #
Convert annotations to their corresponding color for syntax highlighting purposes
data CharacterSet Source #
Instances
detectCharacterSet :: Expr Src a -> CharacterSet Source #
Detect which character set is used for the syntax of an expression If any parts of the expression uses the Unicode syntax, the whole expression is deemed to be using the Unicode syntax.
prettyCharacterSet :: Pretty a => CharacterSet -> Expr Src a -> Doc Ann Source #
Pretty-print an Expr
using the given CharacterSet
.
prettyCharacterSet
largely ignores Note
s. Note
s do however matter for
the layout of let-blocks:
>>>
let inner = Let (Binding Nothing "x" Nothing Nothing Nothing (NaturalLit 1)) (Var (V "x" 0)) :: Expr Src ()
>>>
prettyCharacterSet ASCII (Let (Binding Nothing "y" Nothing Nothing Nothing (NaturalLit 2)) inner)
let y = 2 let x = 1 in x>>>
prettyCharacterSet ASCII (Let (Binding Nothing "y" Nothing Nothing Nothing (NaturalLit 2)) (Note (Src unusedSourcePos unusedSourcePos "") inner))
let y = 2 in let x = 1 in x
This means the structure of parsed let-blocks is preserved.
layout :: Doc ann -> SimpleDocStream ann Source #
Layout using layoutOpts
Tries hard to fit the document into 80 columns.
This also removes trailing space characters (' '
) unless
they are enclosed in an annotation.
layoutOpts :: LayoutOptions Source #
Default layout options
escapeEnvironmentVariable :: Text -> Text Source #
Escape an environment variable if not a valid Bash environment variable