pretty-simple-2.1.0.1: 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

data OutputOptions Source #

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

Constructors

OutputOptions 

Fields

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 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-2.1.0.1-LsGvFQ3g9IN3wIi0t67Glk" 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))))

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.

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

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

renderOutputs :: forall m. MonadReader OutputOptions m => [Output] -> m Builder Source #

Turn a list of Output into a Builder, using the options specified in the OutputOptions.

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

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

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.

renderRaibowParenFor :: 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}]

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 "}]