| 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 | 
Text.Pretty.Simple
Contents
Description
This module contains the functions pPrint, pShow, and pString for
pretty-printing any Haskell data type with a Show instance.
pPrint is the main go-to function when debugging Haskell code.  pShow and
pString are slight variations on pPrint.
pPrint, pShow, and pString will pretty-print in color using ANSI escape
codes.  They look good on a console with a dark (black) background. The
variations pPrintLightBg, pShowLightBg, and pStringLightBg are for
printing in color to a console with a light (white) background.  The variations
pPrintNoColor, pShowNoColor, and pStringNoColor are for pretty-printing
without using color.
The variations pPrintOpt, pShowOpt, and pStringOpt are used when
specifying the OutputOptions.  Most users can ignore these.
See the Examples section at the end of this module for examples of acutally
using pPrint.  See the
README.md
for examples of printing in color.
Synopsis
- pPrint :: (MonadIO m, Show a) => a -> m ()
- pShow :: Show a => a -> Text
- pString :: String -> Text
- pPrintDarkBg :: (MonadIO m, Show a) => a -> m ()
- pShowDarkBg :: Show a => a -> Text
- pStringDarkBg :: String -> Text
- pPrintLightBg :: (MonadIO m, Show a) => a -> m ()
- pShowLightBg :: Show a => a -> Text
- pStringLightBg :: String -> Text
- pPrintNoColor :: (MonadIO m, Show a) => a -> m ()
- pShowNoColor :: Show a => a -> Text
- pStringNoColor :: String -> Text
- pPrintOpt :: (MonadIO m, Show a) => OutputOptions -> a -> m ()
- pShowOpt :: Show a => OutputOptions -> a -> Text
- pStringOpt :: OutputOptions -> String -> Text
- data OutputOptions = OutputOptions {}
- defaultOutputOptionsDarkBg :: OutputOptions
- defaultOutputOptionsLightBg :: OutputOptions
- defaultOutputOptionsNoColor :: OutputOptions
- defaultColorOptionsDarkBg :: ColorOptions
- defaultColorOptionsLightBg :: ColorOptions
Output with color on dark background
pString :: String -> Text Source #
Similar to pShow, but the first argument is a String representing a
 data type that has already been showed.
This will work on any String that is similar to a Haskell data type.  The
 only requirement is that the strings are quoted, and braces, parentheses, and
 brackets are correctly used to represent indentation.  For example,
 pString will correctly pretty-print JSON.
This function is for printing to a dark background.
Aliases for output with color on dark background
Output with color on light background
pPrintLightBg :: (MonadIO m, Show a) => a -> m () Source #
Just like pPrintDarkBg, but for printing to a light background.
pShowLightBg :: Show a => a -> Text Source #
Just like pShowDarkBg, but for printing to a light background.
pStringLightBg :: String -> Text Source #
Just like pStringDarkBg, but for printing to a light background.
Output with NO color
pPrintNoColor :: (MonadIO m, Show a) => a -> m () Source #
Similar to pPrint, but doesn't print in color.  However, data types
 will still be indented nicely.
>>>pPrintNoColor $ Just ["hello", "bye"]Just [ "hello" , "bye" ]
Output With OutputOptions
pPrintOpt :: (MonadIO m, Show a) => OutputOptions -> a -> m () Source #
Similar to pPrint but takes OutputOptions to change how the
 pretty-printing is done.
For example, pPrintOpt can be used to make the indentation much smaller
 than normal.
This is what the normal indentation looks like:
>>>pPrintOpt defaultOutputOptionsNoColor $ Just ("hello", "bye")Just ( "hello" , "bye" )
This is what smaller indentation looks like:
>>>let smallIndent = defaultOutputOptionsNoColor {outputOptionsIndentAmount = 1}>>>pPrintOpt smallIndent $ Just ("hello", "bye")Just ( "hello" , "bye" )
Lines in strings get indented
>>>pPrintOpt defaultOutputOptionsNoColor (1, (2, "foo\nbar\nbaz", 3))( 1 , ( 2 , "foo bar baz" , 3 ) )
Lines get indented even in custom show instances
>>>data Foo = Foo>>>instance Show Foo where show _ = "foo\nbar\nbaz">>>pPrintOpt defaultOutputOptionsNoColor (1, (2, Foo, 3))( 1 , ( 2 , foo bar baz , 3 ) )
pShowOpt :: Show a => OutputOptions -> a -> Text Source #
Like pShow but takes OutputOptions to change how the
 pretty-printing is done.
pStringOpt :: OutputOptions -> String -> Text Source #
Like pString but takes OutputOptions to change how the
 pretty-printing is done.
OutputOptions
data OutputOptions Source #
Data-type wrapping up all the options available when rendering the list
 of Outputs.
Constructors
| OutputOptions | |
| Fields 
 | |
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.
ColorOptions
Additional settings for color options can be found in Text.Pretty.Simple.Internal.Color.
defaultColorOptionsDarkBg :: ColorOptions Source #
Default color options for use on a dark background.
colorQuote is defaultColorQuoteDarkBg. colorString is
 defaultColorStringDarkBg.  colorError is defaultColorErrorDarkBg.
 colorNum is defaultColorNumDarkBg.  colorRainbowParens is
 defaultColorRainboxParensDarkBg.
defaultColorOptionsLightBg :: ColorOptions Source #
Default color options for use on a light background.
colorQuote is defaultColorQuoteLightBg. colorString is
 defaultColorStringLightBg.  colorError is defaultColorErrorLightBg.
 colorNum is defaultColorNumLightBg.  colorRainbowParens is
 defaultColorRainboxParensLightBg.
Examples
Here are some examples of using pPrint on different data types.  You can
 look at these examples to get an idea of what pPrint will output.
The following examples are all using pPrintNoColor instead of pPrint
 because their output is being checked using
 doctest.  pPrint outputs ANSI
 escape codes in order to produce color, so the following examples would be
 hard to read had pPrint been used.
Simple Haskell data type
>>>data Foo a = Foo a String deriving Show
>>>pPrintNoColor $ Foo 3 "hello"Foo 3 "hello"
List
>>>pPrintNoColor $ [1,2,3][ 1 , 2 , 3 ]
Slightly more complicated list
>>>pPrintNoColor $ [ Foo [ (), () ] "hello" ][ Foo [ () , () ] "hello" ]
>>>pPrintNoColor $ [ Foo [ "bar", "baz" ] "hello", Foo [] "bye" ][ Foo [ "bar" , "baz" ] "hello" , Foo [] "bye" ]
Record
>>>:{data Bar b = Bar { barInt :: Int , barA :: b , barList :: [Foo Double] } deriving Show :}
>>>pPrintNoColor $ Bar 1 [10, 11] [Foo 1.1 "", Foo 2.2 "hello"]Bar { barInt = 1 , barA = [ 10 , 11 ] , barList = [ Foo 1.1 "" , Foo 2.2 "hello" ] }
Newtype
>>>newtype Baz = Baz { unBaz :: [String] } deriving Show
>>>pPrintNoColor $ Baz ["hello", "bye"]Baz { unBaz = [ "hello" , "bye" ] }