Copyright | (c) Dennis Gosnell 2016 |
---|---|
License | BSD-style (see LICENSE file) |
Maintainer | cdep.illabout@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data CheckColorTty
- data StringOutputStyle
- data OutputOptions = OutputOptions {}
- defaultOutputOptionsDarkBg :: OutputOptions
- defaultOutputOptionsLightBg :: OutputOptions
- defaultOutputOptionsNoColor :: OutputOptions
- hCheckTTY :: MonadIO m => Handle -> OutputOptions -> m OutputOptions
- layoutString :: OutputOptions -> String -> SimpleDocStream Style
- prettyExprs' :: OutputOptions -> [Expr] -> Doc Annotation
- prettyExprs :: OutputOptions -> [Expr] -> Doc Annotation
- prettyExpr :: OutputOptions -> Expr -> Doc Annotation
- isSimple :: Expr -> Bool
- annotateStyle :: OutputOptions -> SimpleDocStream Annotation -> SimpleDocStream Style
- data Annotation
- escapeNonPrintable :: String -> String
- escape :: Char -> ShowS
- data Tape a = Tape {}
- moveL :: Tape a -> Tape a
- moveR :: Tape a -> Tape a
- data Stream a = a :.. (Stream a)
- streamRepeat :: t -> Stream t
- streamCycle :: NonEmpty a -> Stream a
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.
CheckColorTty | Check if the output |
NoCheckColorTty | Don't check if the output |
Instances
Eq CheckColorTty Source # | |
Defined in Text.Pretty.Simple.Internal.Printer (==) :: CheckColorTty -> CheckColorTty -> Bool # (/=) :: CheckColorTty -> CheckColorTty -> Bool # | |
Show CheckColorTty Source # | |
Defined in Text.Pretty.Simple.Internal.Printer showsPrec :: Int -> CheckColorTty -> ShowS # show :: CheckColorTty -> String # showList :: [CheckColorTty] -> ShowS # | |
Generic CheckColorTty Source # | |
Defined in Text.Pretty.Simple.Internal.Printer 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.Printer |
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.
Literal | Output string literals by printing the source characters exactly. For examples: without this option the printer will insert a newline in
place of |
EscapeNonPrintable | Replace non-printable characters with hexadecimal escape sequences. |
DoNotEscapeNonPrintable | Output non-printable characters without modification. |
Instances
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.
layoutString :: OutputOptions -> String -> SimpleDocStream Style Source #
Parse a string, and generate an intermediate representation,
suitable for passing to any prettyprinter backend.
Used by pString
etc.
prettyExprs' :: OutputOptions -> [Expr] -> Doc Annotation Source #
Slight adjustment of prettyExprs
for the outermost level,
to avoid indenting everything.
prettyExprs :: OutputOptions -> [Expr] -> Doc Annotation Source #
prettyExpr :: OutputOptions -> Expr -> Doc Annotation Source #
isSimple :: Expr -> Bool Source #
Determine whether this expression should be displayed on a single line.
annotateStyle :: OutputOptions -> SimpleDocStream Annotation -> SimpleDocStream Style Source #
Traverse the stream, using a Tape
to keep track of the current style.
data Annotation Source #
An abstract annotation type, representing the various elements we may want to highlight.
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"
escape :: Char -> ShowS Source #
Replace an unprintable character except a newline with a hex escape sequence.
A bidirectional Turing-machine tape: infinite in both directions, with a head pointing to one element.
An infinite list
streamRepeat :: t -> Stream t Source #
Analogous to repeat