pretty-simple-3.3.0.0: pretty printer for data types with a 'Show' instance.

Copyright(c) Dennis Gosnell 2016
LicenseBSD-style (see LICENSE file)
Maintainercdep.illabout@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.Pretty.Simple.Internal.OutputPrinter

Description

 
Synopsis

Documentation

>>> import Text.Pretty.Simple (pPrintString, pPrintStringOpt)

data CheckColorTty Source #

Determines whether pretty-simple should check if the output Handle is a TTY device. Normally, users only want to print in color if the output Handle is a TTY device.

Constructors

CheckColorTty

Check if the output Handle is a TTY device. If the output Handle is a TTY device, determine whether to print in color based on outputOptionsColorOptions. If not, then set outputOptionsColorOptions to Nothing so the output does not get colorized.

NoCheckColorTty

Don't check if the output Handle is a TTY device. Determine whether to colorize the output based solely on the value of outputOptionsColorOptions.

Instances
Eq CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Show CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Generic CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Associated Types

type Rep CheckColorTty :: Type -> Type #

type Rep CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

type Rep CheckColorTty = D1 (MetaData "CheckColorTty" "Text.Pretty.Simple.Internal.OutputPrinter" "pretty-simple-3.3.0.0-4tcvWekYRZRLUgR5XkhTTF" False) (C1 (MetaCons "CheckColorTty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoCheckColorTty" PrefixI False) (U1 :: Type -> Type))

data StringOutputStyle Source #

Control how escaped and non-printable are output for strings.

See outputOptionsStringStyle for what the output looks like with each of these options.

Constructors

Literal

Output string literals by printing the source characters exactly.

For examples: without this option the printer will insert a newline in place of "n", with this options the printer will output '\' and n. Similarly the exact escape codes used in the input string will be replicated, so "65" will be printed as "65" and not A.

EscapeNonPrintable

Replace non-printable characters with hexadecimal escape sequences.

DoNotEscapeNonPrintable

Output non-printable characters without modification.

Instances
Eq StringOutputStyle Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Show StringOutputStyle Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Generic StringOutputStyle Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Associated Types

type Rep StringOutputStyle :: Type -> Type #

type Rep StringOutputStyle Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

type Rep StringOutputStyle = D1 (MetaData "StringOutputStyle" "Text.Pretty.Simple.Internal.OutputPrinter" "pretty-simple-3.3.0.0-4tcvWekYRZRLUgR5XkhTTF" False) (C1 (MetaCons "Literal" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EscapeNonPrintable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DoNotEscapeNonPrintable" PrefixI False) (U1 :: Type -> Type)))

data OutputOptions Source #

Data-type wrapping up all the options available when rendering the list of Outputs.

Constructors

OutputOptions 

Fields

  • outputOptionsIndentAmount :: Int

    Number of spaces to use when indenting. It should probably be either 2 or 4.

  • outputOptionsColorOptions :: Maybe ColorOptions

    If this is Nothing, then don't colorize the output. If this is Just colorOptions, then use colorOptions to colorize the output.

  • outputOptionsStringStyle :: StringOutputStyle

    Controls how string literals are output.

    By default, the pPrint functions escape non-printable characters, but print all printable characters:

    >>> pPrintString "\"A \\x42 Ä \\xC4 \\x1 \\n\""
    "A B Ä Ä \x1 "
    

    Here, you can see that the character A has been printed as-is. x42 has been printed in the non-escaped version, B. The non-printable character x1 has been printed as x1. Newlines will be removed to make the output easier to read.

    This corresponds to the StringOutputStyle called EscapeNonPrintable.

    (Note that in the above and following examples, the characters have to be double-escaped, which makes it somewhat confusing...)

    Another output style is DoNotEscapeNonPrintable. This is similar to EscapeNonPrintable, except that non-printable characters get printed out literally to the screen.

    >>> pPrintStringOpt CheckColorTty defaultOutputOptionsDarkBg{ outputOptionsStringStyle = DoNotEscapeNonPrintable } "\"A \\x42 Ä \\xC4 \\n\""
    "A B Ä Ä "
    

    If you change the above example to contain x1, you can see that it is output as a literal, non-escaped character. Newlines are still removed for readability.

    Another output style is Literal. This just outputs all escape characters.

    >>> pPrintStringOpt CheckColorTty defaultOutputOptionsDarkBg{ outputOptionsStringStyle = Literal } "\"A \\x42 Ä \\xC4 \\x1 \\n\""
    "A \x42 Ä \xC4 \x1 \n"
    

    You can see that all the escape characters get output literally, including newline.

Instances
Eq OutputOptions Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Show OutputOptions Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Generic OutputOptions Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Associated Types

type Rep OutputOptions :: Type -> Type #

type Rep OutputOptions Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

type Rep OutputOptions = D1 (MetaData "OutputOptions" "Text.Pretty.Simple.Internal.OutputPrinter" "pretty-simple-3.3.0.0-4tcvWekYRZRLUgR5XkhTTF" False) (C1 (MetaCons "OutputOptions" PrefixI True) (S1 (MetaSel (Just "outputOptionsIndentAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Just "outputOptionsColorOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ColorOptions)) :*: S1 (MetaSel (Just "outputOptionsStringStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StringOutputStyle))))

defaultOutputOptionsDarkBg :: OutputOptions Source #

Default values for OutputOptions when printing to a console with a dark background. outputOptionsIndentAmount is 4, and outputOptionsColorOptions is defaultColorOptionsDarkBg.

defaultOutputOptionsLightBg :: OutputOptions Source #

Default values for OutputOptions when printing to a console with a light background. outputOptionsIndentAmount is 4, and outputOptionsColorOptions is defaultColorOptionsLightBg.

defaultOutputOptionsNoColor :: OutputOptions Source #

Default values for OutputOptions when printing using using ANSI escape sequences for color. outputOptionsIndentAmount is 4, and outputOptionsColorOptions is Nothing.

hCheckTTY :: MonadIO m => Handle -> OutputOptions -> m OutputOptions Source #

Given OutputOptions, disable colorful output if the given handle is not connected to a TTY.

render :: OutputOptions -> [Output] -> Text Source #

Given OutputOptions and a list of Output, turn the Output into a lazy Text.

renderOutput :: MonadReader OutputOptions m => Output -> m Builder Source #

Render a single Output as a Builder, using the options specified in the OutputOptions.

escapeNonPrintable :: String -> String Source #

Replace non-printable characters with hex escape sequences.

>>> escapeNonPrintable "\x1\x2"
"\\x1\\x2"

Newlines will not be escaped.

>>> escapeNonPrintable "hello\nworld"
"hello\nworld"

Printable characters will not be escaped.

>>> escapeNonPrintable "h\101llo"
"hello"

indentSubsequentLinesWith :: String -> String -> String Source #

>>> indentSubsequentLinesWith "  " "aaa"
"aaa"
>>> indentSubsequentLinesWith "  " "aaa\nbbb\nccc"
"aaa\n  bbb\n  ccc"
>>> indentSubsequentLinesWith "  " ""
""

useColorQuote :: forall m. MonadReader OutputOptions m => m Builder Source #

Produce a Builder corresponding to the ANSI escape sequence for the color for the ", based on whether or not outputOptionsColorOptions is Just or Nothing, and the value of colorQuote.

useColorString :: forall m. MonadReader OutputOptions m => m Builder Source #

Produce a Builder corresponding to the ANSI escape sequence for the color for the characters of a string, based on whether or not outputOptionsColorOptions is Just or Nothing, and the value of colorString.

useColorReset :: forall m. MonadReader OutputOptions m => m Builder Source #

Produce a Builder corresponding to the ANSI escape sequence for resetting the console color back to the default. Produces an empty Builder if outputOptionsColorOptions is Nothing.

renderRainbowParenFor :: MonadReader OutputOptions m => NestLevel -> Builder -> m Builder Source #

Produce a Builder representing the ANSI escape sequence for the color of the rainbow parenthesis, given an input NestLevel and Builder to use as the input character.

If outputOptionsColorOptions is Nothing, then just return the input character. If it is Just, then return the input character colorized.

sequenceFold :: (Monad f, Monoid a, Traversable t) => t (f a) -> f a Source #

This is simply fmap fold . sequence.

modificationsOutputList :: [Output] -> [Output] Source #

A function that performs optimizations and modifications to a list of input Outputs.

An sample of an optimization is removeStartingNewLine which just removes a newline if it is the first item in an Output list.

removeStartingNewLine :: [Output] -> [Output] Source #

Remove a OutputNewLine if it is the first item in the Output list.

>>> removeStartingNewLine [Output 3 OutputNewLine, Output 3 OutputComma]
[Output {outputNestLevel = NestLevel {unNestLevel = 3}, outputOutputType = OutputComma}]

removeTrailingSpacesInOtherBeforeNewLine :: [Output] -> [Output] Source #

Remove trailing spaces from the end of a OutputOther token if it is followed by a OutputNewLine, or if it is the final Output in the list. This function assumes that there is a single OutputOther before any OutputNewLine (and before the end of the list), so it must be run after running compressOthers.

>>> removeTrailingSpacesInOtherBeforeNewLine [Output 2 (OutputOther "foo  "), Output 4 OutputNewLine]
[Output {outputNestLevel = NestLevel {unNestLevel = 2}, outputOutputType = OutputOther "foo"},Output {outputNestLevel = NestLevel {unNestLevel = 4}, outputOutputType = OutputNewLine}]

compressOthers :: [Output] -> [Output] Source #

If there are two subsequent OutputOther tokens, combine them into just one OutputOther.

>>> compressOthers [Output 0 (OutputOther "foo"), Output 0 (OutputOther "bar")]
[Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputOther "foobar"}]

shrinkWhitespaceInOthers :: [Output] -> [Output] Source #

In each OutputOther token, compress multiple whitespaces to just one whitespace.

>>> shrinkWhitespaceInOthers [Output 0 (OutputOther "  hello  ")]
[Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputOther " hello "}]