| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
RIO.PrettyPrint
Synopsis
- class (HasLogFunc env, HasStylesUpdate env) => HasTerm env where
- class HasStylesUpdate env where
- stylesUpdateL :: Lens' env StylesUpdate
- displayPlain :: (Pretty a, HasLogFunc env, HasStylesUpdate env, MonadReader env m, HasCallStack) => Int -> a -> m Utf8Builder
- displayWithColor :: (HasTerm env, Pretty a, MonadReader env m, HasCallStack) => a -> m Utf8Builder
- prettyDebug :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyDebugL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyDebugS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyInfo :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyInfoL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyInfoS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyNote :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyNoteL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyNoteS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyWarn :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyWarnL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyWarnS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyWarnNoIndent :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyWarnNoIndentL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyWarnNoIndentS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyError :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyErrorL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyErrorS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyErrorNoIndent :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m ()
- prettyErrorNoIndentL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m ()
- prettyErrorNoIndentS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m ()
- prettyGeneric :: (HasTerm env, HasCallStack, Pretty b, MonadReader env m, MonadIO m) => LogLevel -> b -> m ()
- prettyWith :: (HasTerm env, HasCallStack, Pretty b, MonadReader env m, MonadIO m) => LogLevel -> (a -> b) -> a -> m ()
- style :: Style -> StyleDoc -> StyleDoc
- displayMilliseconds :: Double -> StyleDoc
- logLevelToStyle :: LogLevel -> Style
- blankLine :: StyleDoc
- bulletedList :: [StyleDoc] -> StyleDoc
- spacedBulletedList :: [StyleDoc] -> StyleDoc
- mkBulletedList :: Bool -> Char -> [StyleDoc] -> StyleDoc
- mkNarrativeList :: Pretty a => Maybe Style -> Bool -> [a] -> [StyleDoc]
- debugBracket :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m, MonadUnliftIO m) => StyleDoc -> m a -> m a
- class Pretty a where
- data StyleDoc
- newtype StyleAnn = StyleAnn (Maybe Style)
- nest :: Int -> StyleDoc -> StyleDoc
- line :: StyleDoc
- linebreak :: StyleDoc
- group :: StyleDoc -> StyleDoc
- softline :: StyleDoc
- softbreak :: StyleDoc
- align :: StyleDoc -> StyleDoc
- hang :: Int -> StyleDoc -> StyleDoc
- indent :: Int -> StyleDoc -> StyleDoc
- encloseSep :: StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc
- (<+>) :: StyleDoc -> StyleDoc -> StyleDoc
- hsep :: [StyleDoc] -> StyleDoc
- vsep :: [StyleDoc] -> StyleDoc
- fillSep :: [StyleDoc] -> StyleDoc
- sep :: [StyleDoc] -> StyleDoc
- hcat :: [StyleDoc] -> StyleDoc
- vcat :: [StyleDoc] -> StyleDoc
- fillCat :: [StyleDoc] -> StyleDoc
- cat :: [StyleDoc] -> StyleDoc
- punctuate :: StyleDoc -> [StyleDoc] -> [StyleDoc]
- fill :: Int -> StyleDoc -> StyleDoc
- fillBreak :: Int -> StyleDoc -> StyleDoc
- enclose :: StyleDoc -> StyleDoc -> StyleDoc -> StyleDoc
- squotes :: StyleDoc -> StyleDoc
- dquotes :: StyleDoc -> StyleDoc
- parens :: StyleDoc -> StyleDoc
- angles :: StyleDoc -> StyleDoc
- braces :: StyleDoc -> StyleDoc
- brackets :: StyleDoc -> StyleDoc
- string :: String -> StyleDoc
- indentAfterLabel :: StyleDoc -> StyleDoc
- wordDocs :: String -> [StyleDoc]
- flow :: String -> StyleDoc
- data Style
Type classes for optionally colored terminal output
class (HasLogFunc env, HasStylesUpdate env) => HasTerm env where Source #
Instances
| HasTerm SimplePrettyApp Source # | |
Defined in RIO.PrettyPrint.Simple | |
class HasStylesUpdate env where Source #
Environment values with a styles update.
Since: 0.1.0.0
Methods
stylesUpdateL :: Lens' env StylesUpdate Source #
Instances
| HasStylesUpdate SimplePrettyApp Source # | |
Defined in RIO.PrettyPrint.Simple Methods stylesUpdateL :: Lens' SimplePrettyApp StylesUpdate Source # | |
| HasStylesUpdate StylesUpdate Source # | |
Defined in RIO.PrettyPrint.StylesUpdate Methods | |
Pretty printing functions
displayPlain :: (Pretty a, HasLogFunc env, HasStylesUpdate env, MonadReader env m, HasCallStack) => Int -> a -> m Utf8Builder Source #
displayWithColor :: (HasTerm env, Pretty a, MonadReader env m, HasCallStack) => a -> m Utf8Builder Source #
Logging based on pretty-print typeclass
The pretty... functions come in three varieties:
- The normal variety, with a single styled document;
- The
Lvariety. The listed styled documents are concatenated withfillSep; and - The
Svariety.flowis applied to theString.
Pretty message at log level LevelDebug.
prettyDebug :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () Source #
prettyDebugL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () Source #
prettyDebugS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () Source #
Pretty message at log level LevelInfo.
prettyInfo :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () Source #
prettyInfoL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () Source #
prettyInfoS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () Source #
Pretty messages at log level LevelInfo, starting on a new line with
label Note:, with the message indented after the label.
prettyNote :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () Source #
prettyNoteL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () Source #
prettyNoteS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () Source #
Pretty messages at log level LevelWarn, starting on a new line with
label Warning:, with or without the message indented after the label.
prettyWarn :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () Source #
prettyWarnL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () Source #
prettyWarnS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyWarnNoIndent :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () Source #
prettyWarnNoIndentL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () Source #
prettyWarnNoIndentS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () Source #
Pretty messages at log level LevelError, starting on a new line with
label Error:, with or without the message indented after the label.
prettyError :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () Source #
prettyErrorL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () Source #
prettyErrorS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyErrorNoIndent :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => StyleDoc -> m () Source #
prettyErrorNoIndentL :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => [StyleDoc] -> m () Source #
prettyErrorNoIndentS :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m) => String -> m () Source #
Pretty messages at the specified log level.
prettyGeneric :: (HasTerm env, HasCallStack, Pretty b, MonadReader env m, MonadIO m) => LogLevel -> b -> m () Source #
prettyWith :: (HasTerm env, HasCallStack, Pretty b, MonadReader env m, MonadIO m) => LogLevel -> (a -> b) -> a -> m () Source #
Semantic styling functions
These are used rather than applying colors or other styling directly, to provide consistency.
Display as milliseconds in style Good.
logLevelToStyle :: LogLevel -> Style Source #
Formatting utils
bulletedList :: [StyleDoc] -> StyleDoc Source #
Display a bulleted list of StyleDoc with * as the bullet point.
spacedBulletedList :: [StyleDoc] -> StyleDoc Source #
Display a bulleted list of StyleDoc with a blank line between
each and * as the bullet point.
Arguments
| :: Bool | Spaced with a blank line between each item? |
| -> Char | The character to act as the bullet point. |
| -> [StyleDoc] | |
| -> StyleDoc |
Display a bulleted list of StyleDoc, spaced with blank lines or not,
given a character for the bullet point.
Since: 0.1.6.0
Arguments
| :: Pretty a | |
| => Maybe Style | Style the items in the list? |
| -> Bool | Use a serial comma? |
| -> [a] | |
| -> [StyleDoc] |
A helper function to yield a narrative list from a list of items, with a
final fullstop. For example, helps produce the output
"apple, ball and cat." (no serial comma) or "apple, ball, and cat."
(serial comma) from ["apple", "ball", "cat"].
Since: 0.1.4.0
debugBracket :: (HasCallStack, HasTerm env, MonadReader env m, MonadIO m, MonadUnliftIO m) => StyleDoc -> m a -> m a Source #
debug message action brackets any output of the specified action with
an initial and final message at log level LevelDebug. The initial message
is prefixed with the label Start:. The final message is prefixed with
information about the duration of the action in milliseconds (ms) and, if
an exception is thrown by the action, the exception. For example:
Start: <message> <output of action> Finished in ...ms: <message>
or:
Start: <message> <output of action> Finished with exception in ...ms: <message> Exception thrown: <exception_message>
Re-exports from Text.PrettyPrint.Leijen.Extended
Minimal complete definition
Nothing
Instances
| Pretty ModuleName Source # | |
Defined in Text.PrettyPrint.Leijen.Extended Methods pretty :: ModuleName -> StyleDoc Source # | |
| Pretty Arch Source # | |
| Pretty OS Source # | |
| Pretty PrettyException Source # | |
Defined in RIO.PrettyPrint.PrettyException Methods pretty :: PrettyException -> StyleDoc Source # | |
| Pretty StyleDoc Source # | |
| Pretty (SomeBase Dir) Source # | |
| Pretty (SomeBase File) Source # | |
| Pretty (Path b Dir) Source # | |
| Pretty (Path b File) Source # | |
A document annotated by a style.
A style annotation.
The line document advances to the next line and indents to the current
nesting level. Document line behaves like (fromString " ") if the line
break is undone by group.
group :: StyleDoc -> StyleDoc Source #
The group combinator is used to specify alternative layouts. The document
(group x) undoes all line breaks in document x. The resulting line is
added to the current line if that fits the page. Otherwise, the document x
is rendered without any changes.
The document softline behaves like (fromString " ") if the resulting
output fits the page, otherwise it behaves like line.
softline = group line
align :: StyleDoc -> StyleDoc Source #
The document (align x) renders document x with the nesting level set to
the current column. It is used for example to implement hang.
As an example, we will put a document right above another one, regardless of the current nesting level:
x $$ y = align (x <> line <> y)
test = fromString "hi" <+> (fromString "nice" $$ fromString "world")
which will be layed out as:
hi nice world
hang :: Int -> StyleDoc -> StyleDoc Source #
The hang combinator implements hanging indentation. The document
(hang i x) renders document x with a nesting level set to the current
column plus i. The following example uses hanging indentation for some
text:
test = hang 4 (fillSep (map fromString
(words "the hang combinator indents these words !")))Which lays out on a page with a width of 20 characters as:
the hang combinator
indents these
words !
The hang combinator is implemented as:
hang i x = align (nest i x)
indent :: Int -> StyleDoc -> StyleDoc Source #
The document (indent i x) indents document x with i spaces.
test = indent 4 (fillSep (map fromString
(words "the indent combinator indents these words !")))Which lays out with a page width of 20 as:
the indent
combinator
indents these
words !
encloseSep :: StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc Source #
The document (encloseSep l r sep xs) concatenates the documents xs
separated by sep and encloses the resulting document by l and r. The
documents are rendered horizontally if that fits the page. Otherwise they are
aligned vertically. All separators are put in front of the elements. For
example, the combinator list can be defined with encloseSep:
list xs = encloseSep lbracket rbracket comma xs test = fromString "list" <+> (list (map int [10, 200, 3000]))
Which is layed out with a page width of 20 as:
list [10,200,3000]
But when the page width is 15, it is layed out as:
list [10
,200
,3000]
(<+>) :: StyleDoc -> StyleDoc -> StyleDoc Source #
The document (x <+> y) concatenates document x and y with a
(fromString " ") in between. (infixr 6)
hsep :: [StyleDoc] -> StyleDoc Source #
The document (hsep xs) concatenates all documents xs horizontally with
(.<+>)
vsep :: [StyleDoc] -> StyleDoc Source #
The document (vsep xs) concatenates all documents xs vertically with
(<> line <>). If a group undoes the line breaks inserted by vsep,
all documents are separated with a space.
someText = map fromString (words ("text to lay out"))
test = fromString "some" <+> vsep someTextThis is layed out as:
some text to lay out
The align combinator can be used to align the documents under their first
element
test = fromString "some" <+> align (vsep someText)
Which is printed as:
some text
to
lay
out
sep :: [StyleDoc] -> StyleDoc Source #
The document (sep xs) concatenates all documents xs either horizontally
with (<+>), if it fits the page, or vertically with (<> line <>).
sep xs = group (vsep xs)
hcat :: [StyleDoc] -> StyleDoc Source #
The document (hcat xs) concatenates all documents xs horizontally with
(<>).
fillCat :: [StyleDoc] -> StyleDoc Source #
The document (fillCat xs) concatenates documents xs horizontally with
(<>) as long as its fits the page, than inserts a linebreak and
continues doing that for all documents in xs.
fillCat xs = foldr (<> softbreak <>) mempty xs
cat :: [StyleDoc] -> StyleDoc Source #
The document (cat xs) concatenates all documents xs either
horizontally with (<>), if it fits the page, or vertically with
(<> linebreak <>).
cat xs = group (vcat xs)
punctuate :: StyleDoc -> [StyleDoc] -> [StyleDoc] Source #
(punctuate p xs) concatenates all documents in xs with document p
except for the last document.
someText = map fromString ["words", "in", "a", "tuple"] test = parens (align (cat (punctuate comma someText)))
This is layed out on a page width of 20 as:
(words,in,a,tuple)
But when the page width is 15, it is layed out as:
(words, in, a, tuple)
(If you want put the commas in front of their elements instead of at the end,
you should use encloseSep.)
fill :: Int -> StyleDoc -> StyleDoc Source #
The document (fill i x) renders document x. It than appends
(fromString " ")s until the width is equal to i. If the width of x
is already larger, nothing is appended. This combinator is quite useful in
practice to output a list of bindings. The following example demonstrates
this.
types = [ ("empty", "Doc a")
, ("nest", "Int -> Doc a -> Doc a")
, ("linebreak", "Doc a")
]
ptype (name, tp) =
fill 6 (fromString name) <+> fromString "::" <+> fromString tp
test = fromString "let" <+> align (vcat (map ptype types))Which is layed out as:
let empty :: Doc a
nest :: Int -> Doc a -> Doc a
linebreak :: Doc a
fillBreak :: Int -> StyleDoc -> StyleDoc Source #
The document (fillBreak i x) first renders document x. It then appends
(fromString " ")s until the width is equal to i. If the width of x
is already larger than i, the nesting level is increased by i and a
line is appended. When we redefine ptype in the previous example to use
fillBreak, we get a useful variation of the previous output:
ptype (name, tp) = fillBreak 6 (fromString name) <+> fromString "::" <+> fromString tp
The output will now be:
let empty :: Doc a
nest :: Int -> Doc a -> Doc a
linebreak
:: Doc a
enclose :: StyleDoc -> StyleDoc -> StyleDoc -> StyleDoc Source #
The document (enclose l r x) encloses document x between documents l
and r using (<>).
enclose l r x = l <> x <> r
squotes :: StyleDoc -> StyleDoc Source #
Document (squotes x) encloses document x with single quotes "'".
dquotes :: StyleDoc -> StyleDoc Source #
Document (dquotes x) encloses document x with double quotes '"'.
parens :: StyleDoc -> StyleDoc Source #
Document (parens x) encloses document x in parenthesis, "(" and
")".
angles :: StyleDoc -> StyleDoc Source #
Document (angles x) encloses document x in angles, "<" and ">".
braces :: StyleDoc -> StyleDoc Source #
Document (braces x) encloses document x in braces, "{" and "}".
brackets :: StyleDoc -> StyleDoc Source #
Document (brackets x) encloses document x in square brackets, "[" and
"]".
string :: String -> StyleDoc Source #
The document string s concatenates all characters in s using line for
newline characters and fromString for all other characters. It is used
whenever the text contains newline characters.
Since: 0.1.4.0
indentAfterLabel :: StyleDoc -> StyleDoc Source #
Use after a label and before the rest of what's being labelled for consistent spacingindentingetc.
For example this is used after "Warning:" in warning messages.
Re-exports from RIO.PrettyPrint.Types.PrettyPrint
Type representing styles of output.
Constructors
| Error | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
| Warning | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
| Info | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
| Debug | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
| OtherLevel | Intended to be used sparingly, not to style entire long messages. For
example, to style the |
| Good | Style in a way to emphasize that it is a particularly good thing. |
| Shell | Style as a shell command, i.e. when suggesting something to the user that should be typed in directly as written. |
| File | Style as a filename. See |
| Url | Style as a URL. |
| Dir | Style as a directory name. See |
| Recommendation | Style used to highlight part of a recommended course of action. |
| Current | Style in a way that emphasizes that it is related to a current thing. For example, to report the current package that is being processed when outputting the name of it. |
| Target | Style used the highlight the target of a course of action. |
| Module | Style as a module name. |
| PkgComponent | Style used to highlight the named component of a package. |
| Secondary | Style for secondary content. For example, to style timestamps. |
| Highlight | Intended to be used sparingly, not to style entire long messages. For
example, to style the duration in a |