dhall-1.42.0: A configuration language guaranteed to terminate
Safe HaskellSafe-Inferred
LanguageHaskell2010

Dhall.Pretty

Contents

Description

This module contains logic for pretty-printing expressions, including support for syntax highlighting

Synopsis

Pretty

data Ann #

Annotation type used to tag elements in a pretty-printed document for syntax highlighting purposes

Constructors

Keyword

Used for syntactic keywords

Syntax

Syntax punctuation such as commas, parenthesis, and braces

Label

Record labels

Literal

Literals such as integers and strings

Builtin

Builtin types and values

Operator

Operators

Instances

Instances details
Show Ann # 
Instance details

Defined in Dhall.Pretty.Internal

Methods

showsPrec :: Int -> Ann -> ShowS #

show :: Ann -> String #

showList :: [Ann] -> ShowS #

annToAnsiStyle :: Ann -> AnsiStyle #

Convert annotations to their corresponding color for syntax highlighting purposes

prettyExpr :: Pretty a => Expr s a -> Doc Ann #

Pretty print an expression

data CharacterSet #

This type determines whether to render code as ASCII or Unicode

Constructors

ASCII 
Unicode 

Instances

Instances details
FromJSON CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Data CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CharacterSet -> c CharacterSet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CharacterSet #

toConstr :: CharacterSet -> Constr #

dataTypeOf :: CharacterSet -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CharacterSet) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CharacterSet) #

gmapT :: (forall b. Data b => b -> b) -> CharacterSet -> CharacterSet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CharacterSet -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CharacterSet -> r #

gmapQ :: (forall d. Data d => d -> u) -> CharacterSet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CharacterSet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CharacterSet -> m CharacterSet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CharacterSet -> m CharacterSet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CharacterSet -> m CharacterSet #

Monoid CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Semigroup CharacterSet #

Since ASCII is a subset of Unicode, if either argument is Unicode, the result is Unicode

Instance details

Defined in Dhall.Pretty.Internal

Generic CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Associated Types

type Rep CharacterSet :: Type -> Type #

Show CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Methods

showsPrec :: Int -> CharacterSet -> ShowS #

show :: CharacterSet -> String #

showList :: [CharacterSet] -> ShowS #

NFData CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Methods

rnf :: CharacterSet -> ()

Eq CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Ord CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Lift CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

Methods

lift :: Quote m => CharacterSet -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => CharacterSet -> Code m CharacterSet #

type Rep CharacterSet # 
Instance details

Defined in Dhall.Pretty.Internal

type Rep CharacterSet = D1 ('MetaData "CharacterSet" "Dhall.Pretty.Internal" "dhall-1.42.0-KYLP0Bk1OLT52T5U2EOzRV" 'False) (C1 ('MetaCons "ASCII" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unicode" 'PrefixI 'False) (U1 :: Type -> Type))

detectCharacterSet :: Expr Src a -> CharacterSet #

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 #

Pretty-print an Expr using the given CharacterSet.

prettyCharacterSet largely ignores Notes. Notes 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 #

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 #

Default layout options

escapeEnvironmentVariable :: Text -> Text #

Escape an environment variable if not a valid Bash environment variable

escapeLabel :: Bool -> Text -> Text #

Escape a label if it is not valid when unquoted

temporalToText :: Pretty a => Expr s a -> Maybe Text #

Convert an expression representing a temporal value to Text, if possible

This is used by downstream integrations (e.g. `dhall-json` for treating temporal values as strings