| 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 |
Text.Pretty.Simple.Internal.Printer
Description
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
- layoutStringAbstract :: OutputOptions -> String -> SimpleDocStream Annotation
- 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.
Constructors
| CheckColorTty | Check if the output |
| NoCheckColorTty | Don't check if the output |
Instances
| Generic CheckColorTty Source # | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
| |||||
| Show CheckColorTty Source # | |||||
Defined in Text.Pretty.Simple.Internal.Printer Methods showsPrec :: Int -> CheckColorTty -> ShowS # show :: CheckColorTty -> String # showList :: [CheckColorTty] -> ShowS # | |||||
| Eq CheckColorTty Source # | |||||
Defined in Text.Pretty.Simple.Internal.Printer Methods (==) :: CheckColorTty -> CheckColorTty -> Bool # (/=) :: CheckColorTty -> CheckColorTty -> Bool # | |||||
| 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.
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 |
| 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 Outputs.
Constructors
| OutputOptions | |
Fields
| |
Instances
| Generic OutputOptions Source # | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
| |||||
| Show OutputOptions Source # | |||||
Defined in Text.Pretty.Simple.Internal.Printer Methods showsPrec :: Int -> OutputOptions -> ShowS # show :: OutputOptions -> String # showList :: [OutputOptions] -> ShowS # | |||||
| Eq OutputOptions Source # | |||||
Defined in Text.Pretty.Simple.Internal.Printer Methods (==) :: OutputOptions -> OutputOptions -> Bool # (/=) :: OutputOptions -> OutputOptions -> Bool # | |||||
| type Rep OutputOptions Source # | |||||
Defined in Text.Pretty.Simple.Internal.Printer type Rep OutputOptions = D1 ('MetaData "OutputOptions" "Text.Pretty.Simple.Internal.Printer" "pretty-simple-4.1.4.0-IyMxnqtw63A2xOsPIc2Tfl" 'False) (C1 ('MetaCons "OutputOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "outputOptionsIndentAmount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "outputOptionsPageWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "outputOptionsCompact") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "outputOptionsCompactParens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "outputOptionsInitialIndent") '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.
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.
Instances
| Show Annotation Source # | |
Defined in Text.Pretty.Simple.Internal.Printer Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
| Eq Annotation Source # | |
Defined in Text.Pretty.Simple.Internal.Printer | |
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.
Constructors
| Tape | |
An infinite list
streamRepeat :: t -> Stream t Source #
Analogous to repeat