rio-prettyprint-0.1.8.0: Pretty-printing for RIO
Safe HaskellSafe-Inferred
LanguageHaskell2010

RIO.PrettyPrint

Synopsis

Type classes for optionally colored terminal output

class HasStylesUpdate env where Source #

Environment values with a styles update.

Since: 0.1.0.0

Pretty printing functions

Logging based on pretty-print typeclass

The pretty... functions come in three varieties:

  • The normal variety, with a single styled document;
  • The L variety. The listed styled documents are concatenated with fillSep; and
  • The S variety. flow is applied to the String.

Pretty message at log level LevelDebug.

Pretty message at log level LevelInfo.

Pretty messages at log level LevelInfo, starting on a new line with label Note:, with the message indented after the label.

Pretty messages at log level LevelWarn, starting on a new line with label Warning:, with or without the message indented after the label.

Pretty messages at log level LevelError, starting on a new line with label Error:, with or without the message indented after the label.

Pretty messages at the specified log level.

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.

style :: Style -> StyleDoc -> StyleDoc Source #

Annotate a StyleDoc with a Style.

displayMilliseconds Source #

Arguments

:: Double

Amount of time in seconds.

-> StyleDoc 

Display as milliseconds in style Good.

logLevelToStyle :: LogLevel -> Style Source #

The Style intended to be associated with a LogLevel.

Since: 0.1.1.0

Formatting utils

blankLine :: StyleDoc Source #

A blank line.

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.

mkBulletedList Source #

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

mkNarrativeList Source #

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

class Pretty a where Source #

Minimal complete definition

Nothing

Methods

pretty :: a -> StyleDoc Source #

default pretty :: Show a => a -> StyleDoc Source #

Instances

Instances details
Pretty ModuleName Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Pretty Arch Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Methods

pretty :: Arch -> StyleDoc Source #

Pretty OS Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Methods

pretty :: OS -> StyleDoc Source #

Pretty PrettyException Source # 
Instance details

Defined in RIO.PrettyPrint.PrettyException

Pretty StyleDoc Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Pretty (SomeBase Dir) Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Pretty (SomeBase File) Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Pretty (Path b Dir) Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Methods

pretty :: Path b Dir -> StyleDoc Source #

Pretty (Path b File) Source # 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

Methods

pretty :: Path b File -> StyleDoc Source #

data StyleDoc Source #

A document annotated by a style.

newtype StyleAnn Source #

A style annotation.

Constructors

StyleAnn (Maybe Style) 

nest :: Int -> StyleDoc -> StyleDoc Source #

The document (nest i x) renders document x with the current indentation level increased by i (See also hang, align and indent).

   nest 2 (fromString "hello" <> line <> fromString "world")
<> line
<> fromString "!"

outputs as:

hello
  world
!

line :: StyleDoc Source #

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.

linebreak :: StyleDoc Source #

The linebreak document advances to the next line and indents to the current nesting level. Document linebreak behaves like mempty 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.

softline :: StyleDoc Source #

The document softline behaves like (fromString " ") if the resulting output fits the page, otherwise it behaves like line.

softline = group line

softbreak :: StyleDoc Source #

The document softbreak behaves like mempty if the resulting output fits the page, otherwise it behaves like line.

softbreak = group linebreak

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 someText

This 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

fillSep :: [StyleDoc] -> StyleDoc Source #

The document (fillSep xs) concatenates documents xs horizontally with (<+>) as long as its fits the page, than inserts a line and continues doing that for all documents in xs.

fillSep xs = foldr (<> softline <>) mempty xs

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 (<>).

vcat :: [StyleDoc] -> StyleDoc Source #

The document (vcat xs) concatenates all documents xs vertically with (<> linebreak <>). If a group undoes the line breaks inserted by vcat, all documents are directly concatenated.

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.

wordDocs :: String -> [StyleDoc] Source #

Make a StyleDoc from each word in a String

flow :: String -> StyleDoc Source #

Wordwrap a String

Re-exports from RIO.PrettyPrint.Types.PrettyPrint

data Style Source #

Type representing styles of output.

Constructors

Error

Intended to be used sparingly, not to style entire long messages. For example, to style the Error: or [error] label for an error message, not the entire message.

Warning

Intended to be used sparingly, not to style entire long messages. For example, to style the Warning: or [warn] label for a warning message, not the entire message.

Info

Intended to be used sparingly, not to style entire long messages. For example, to style the [info] label for an info message, not the entire message.

Debug

Intended to be used sparingly, not to style entire long messages. For example, to style the [debug] label for a debug message, not the entire message.

OtherLevel

Intended to be used sparingly, not to style entire long messages. For example, to style the [...] label for an other log level message, not the entire message.

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 Dir for directories.

Url

Style as a URL.

Dir

Style as a directory name. See File for files.

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 Finished process in ... ms message.

Instances

Instances details
Semigroup Style Source #

The first style overrides the second.

Instance details

Defined in RIO.PrettyPrint.Types

Methods

(<>) :: Style -> Style -> Style #

sconcat :: NonEmpty Style -> Style #

stimes :: Integral b => b -> Style -> Style #

Bounded Style Source # 
Instance details

Defined in RIO.PrettyPrint.Types

Enum Style Source # 
Instance details

Defined in RIO.PrettyPrint.Types

Ix Style Source # 
Instance details

Defined in RIO.PrettyPrint.Types

Show Style Source # 
Instance details

Defined in RIO.PrettyPrint.Types

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Eq Style Source # 
Instance details

Defined in RIO.PrettyPrint.Types

Methods

(==) :: Style -> Style -> Bool #

(/=) :: Style -> Style -> Bool #

Ord Style Source # 
Instance details

Defined in RIO.PrettyPrint.Types

Methods

compare :: Style -> Style -> Ordering #

(<) :: Style -> Style -> Bool #

(<=) :: Style -> Style -> Bool #

(>) :: Style -> Style -> Bool #

(>=) :: Style -> Style -> Bool #

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #