Copyright | (c) Dennis Gosnell 2016 |
---|---|
License | BSD-style (see LICENSE file) |
Maintainer | cdep.illabout@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data CheckColorTty
- data OutputOptions = OutputOptions {}
- defaultOutputOptionsDarkBg :: OutputOptions
- defaultOutputOptionsLightBg :: OutputOptions
- defaultOutputOptionsNoColor :: OutputOptions
- hCheckTTY :: MonadIO m => Handle -> OutputOptions -> m OutputOptions
- render :: OutputOptions -> [Output] -> Text
- renderOutput :: MonadReader OutputOptions m => Output -> m Builder
- escapeNonPrintable :: String -> String
- escape :: Char -> ShowS
- indentSubsequentLinesWith :: String -> String -> String
- useColorQuote :: forall m. MonadReader OutputOptions m => m Builder
- useColorString :: forall m. MonadReader OutputOptions m => m Builder
- useColorError :: forall m. MonadReader OutputOptions m => m Builder
- useColorNum :: forall m. MonadReader OutputOptions m => m Builder
- useColorReset :: forall m. MonadReader OutputOptions m => m Builder
- renderRainbowParenFor :: MonadReader OutputOptions m => NestLevel -> Builder -> m Builder
- useColorRainbowParens :: forall m. MonadReader OutputOptions m => NestLevel -> m Builder
- sequenceFold :: (Monad f, Monoid a, Traversable t) => t (f a) -> f a
- modificationsOutputList :: [Output] -> [Output]
- removeStartingNewLine :: [Output] -> [Output]
- removeTrailingSpacesInOtherBeforeNewLine :: [Output] -> [Output]
- compressOthers :: [Output] -> [Output]
- shrinkWhitespaceInOthers :: [Output] -> [Output]
- shrinkWhitespaceInOther :: Output -> Output
- shrinkWhitespace :: String -> String
Documentation
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.
CheckColorTty | Check if the output |
NoCheckColorTty | Don't check if the output |
Instances
Eq CheckColorTty Source # | |
Defined in Text.Pretty.Simple.Internal.OutputPrinter (==) :: CheckColorTty -> CheckColorTty -> Bool # (/=) :: CheckColorTty -> CheckColorTty -> Bool # | |
Show CheckColorTty Source # | |
Defined in Text.Pretty.Simple.Internal.OutputPrinter showsPrec :: Int -> CheckColorTty -> ShowS # show :: CheckColorTty -> String # showList :: [CheckColorTty] -> ShowS # | |
Generic CheckColorTty Source # | |
Defined in Text.Pretty.Simple.Internal.OutputPrinter type Rep CheckColorTty :: Type -> Type # from :: CheckColorTty -> Rep CheckColorTty x # to :: Rep CheckColorTty x -> CheckColorTty # | |
type Rep CheckColorTty Source # | |
Defined in Text.Pretty.Simple.Internal.OutputPrinter |
data OutputOptions Source #
Data-type wrapping up all the options available when rendering the list
of Output
s.
OutputOptions | |
|
Instances
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
.
useColorError :: forall m. MonadReader OutputOptions m => m Builder Source #
useColorNum :: forall m. MonadReader OutputOptions m => m Builder Source #
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.
useColorRainbowParens :: forall m. MonadReader OutputOptions m => NestLevel -> m Builder Source #
sequenceFold :: (Monad f, Monoid a, Traversable t) => t (f a) -> f a Source #
modificationsOutputList :: [Output] -> [Output] Source #
A function that performs optimizations and modifications to a list of
input Output
s.
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 "}]
shrinkWhitespace :: String -> String Source #