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

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.

pPrint and pPrintLightBg will intelligently decide whether or not to use ANSI escape codes for coloring depending on whether or not the output is a TTY. This works in most cases. If you want to force color output, you can use the pPrintForceColor or pPrintForceColorLightBg functions.

The variations pPrintOpt, pShowOpt, and pStringOpt are used when specifying the OutputOptions. Most users can ignore these.

There are a few other functions available that are similar to pPrint.

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

Output with color on dark background

pPrint :: (MonadIO m, Show a) => a -> m () Source #

Pretty-print any data type that has a Show instance.

If you've never seen MonadIO before, you can think of this function as having the following type signature:

 pPrint :: Show a => a -> IO ()

This function will only use colors if it detects it's printing to a TTY.

This function is for printing to a dark background. Use pPrintLightBg for printing to a terminal with a light background. Different colors are used.

Prints to stdout. Use pHPrint to print to a different Handle.

>>> pPrint [Just (1, "hello")]
[ Just
    ( 1
    , "hello"
    )
]

pHPrint :: (MonadIO m, Show a) => Handle -> a -> m () Source #

Similar to pPrint, but take a Handle to print to.

>>> pHPrint stdout [Just (1, "hello")]
[ Just
    ( 1
    , "hello"
    )
]

pPrintString :: MonadIO m => String -> m () Source #

Similar to pPrint, but the first argument is a String representing a data type that has already been showed.

>>> pPrintString $ show [ Just (1, "hello"), Nothing ]
[ Just
    ( 1
    , "hello"
    )
, Nothing
]

pHPrintString :: MonadIO m => Handle -> String -> m () Source #

Similar to pHPrintString, but take a Handle to print to.

>>> pHPrintString stdout $ show [ Just (1, "hello"), Nothing ]
[ Just
    ( 1
    , "hello"
    )
, Nothing
]

pPrintForceColor :: (MonadIO m, Show a) => a -> m () Source #

Similar to pPrint, but print in color regardless of whether the output goes to a TTY or not.

See pPrint for an example of how to use this function.

pHPrintForceColor :: (MonadIO m, Show a) => Handle -> a -> m () Source #

Similar to pPrintForceColor, but take a Handle to print to.

See pHPrint for an example of how to use this function.

pPrintStringForceColor :: MonadIO m => String -> m () Source #

Similar to pPrintString, but print in color regardless of whether the output goes to a TTY or not.

See pPrintString for an example of how to use this function.

pHPrintStringForceColor :: MonadIO m => Handle -> String -> m () Source #

Similar to pHPrintString, but print in color regardless of whether the output goes to a TTY or not.

See pHPrintString for an example of how to use this function.

pShow :: Show a => a -> Text Source #

Similar to pPrintForceColor, but just return the resulting pretty-printed data type as a Text instead of printing it to the screen.

This function is for printing to a dark background.

See pShowNoColor for an example of how to use this function.

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.

See pStringNoColor for an example of how to use this function.

Aliases for output with color on dark background

pPrintDarkBg :: (MonadIO m, Show a) => a -> m () Source #

Alias for pPrint.

pHPrintDarkBg :: (MonadIO m, Show a) => Handle -> a -> m () Source #

Alias for pHPrint.

pPrintForceColorDarkBg :: (MonadIO m, Show a) => a -> m () Source #

Alias for pPrintForceColor.

pShowDarkBg :: Show a => a -> Text Source #

Alias for pShow.

Output with color on light background

pPrintLightBg :: (MonadIO m, Show a) => a -> m () Source #

Just like pPrintDarkBg, but for printing to a light background.

pHPrintLightBg :: (MonadIO m, Show a) => Handle -> a -> m () Source #

Just like pHPrintDarkBg, but for printing to a light background.

pPrintStringLightBg :: MonadIO m => String -> m () Source #

Just like pPrintStringDarkBg, but for printing to a light background.

pHPrintStringLightBg :: MonadIO m => Handle -> String -> m () Source #

Just like pHPrintStringDarkBg, but for printing to a light background.

pPrintForceColorLightBg :: (MonadIO m, Show a) => a -> m () Source #

Just like pPrintForceColorDarkBg, but for printing to a light background.

pHPrintForceColorLightBg :: (MonadIO m, Show a) => Handle -> a -> m () Source #

Just like pHPrintForceColorDarkBg, but for printing to a light background.

pPrintStringForceColorLightBg :: MonadIO m => String -> m () Source #

Just like pPrintStringForceColorDarkBg, but for printing to a light background.

pHPrintStringForceColorLightBg :: MonadIO m => Handle -> String -> m () Source #

Just like pHPrintStringForceColorDarkBg, 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"
    ]

pHPrintNoColor :: (MonadIO m, Show a) => Handle -> a -> m () Source #

Like pPrintNoColor, but take a Handle to determine where to print to.

>>> pHPrintNoColor stdout $ Just ["hello", "bye"]
Just
    [ "hello"
    , "bye"
    ]

pPrintStringNoColor :: MonadIO m => String -> m () Source #

Similar to pPrintString, but doesn't print in color. However, data types will still be indented nicely.

>>> pPrintStringNoColor $ show $ Just ["hello", "bye"]
Just
    [ "hello"
    , "bye"
    ]

pHPrintStringNoColor :: MonadIO m => Handle -> String -> m () Source #

Like pPrintStringNoColor, but take a Handle to determine where to print to.

>>> pHPrintStringNoColor stdout $ show $ Just ["hello", "bye"]
Just
    [ "hello"
    , "bye"
    ]

pShowNoColor :: Show a => a -> Text Source #

Like pShow, but without color.

>>> pShowNoColor [ Nothing, Just (1, "hello") ]
"[ Nothing\n, Just\n    ( 1\n    , \"hello\"\n    )\n]"

pStringNoColor :: String -> Text Source #

LIke pString, but without color.

>>> pStringNoColor $ show [1, 2, 3]
"[ 1\n, 2\n, 3\n]"

Output With OutputOptions

pPrintOpt :: (MonadIO m, Show a) => CheckColorTty -> 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 NoCheckColorTty defaultOutputOptionsNoColor $ Just ("hello", "bye")
Just
    ( "hello"
    , "bye"
    )

This is what smaller indentation looks like:

>>> let smallIndent = defaultOutputOptionsNoColor {outputOptionsIndentAmount = 1}
>>> pPrintOpt CheckColorTty smallIndent $ Just ("hello", "bye")
Just
 ( "hello"
 , "bye"
 )

Lines in strings get indented

>>> pPrintOpt NoCheckColorTty 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 CheckColorTty defaultOutputOptionsNoColor (1, (2, Foo, 3))
( 1
,
    ( 2
    , foo
      bar
      baz
    , 3
    )
)

CheckColorTty determines whether to test stdout for whether or not it is connected to a TTY.

If set to NoCheckColorTty, then pPrintOpt won't check if stdout is a TTY. It will print in color depending on the value of outputOptionsColorOptions.

If set to CheckColorTty, then pPrintOpt will check if stdout is conneted to a TTY. If stdout is determined to be connected to a TTY, then it will print in color depending on the value of outputOptionsColorOptions. If stdout is determined to NOT be connected to a TTY, then it will NOT print in color, regardless of the value of outputOptionsColorOptions.

pHPrintOpt :: (MonadIO m, Show a) => CheckColorTty -> OutputOptions -> Handle -> a -> m () Source #

Similar to pPrintOpt, but take a Handle to determine where to print to.

pPrintStringOpt :: MonadIO m => CheckColorTty -> OutputOptions -> String -> m () Source #

Similar to pPrintOpt, but the last argument is a string representing a data structure that has already been showed.

>>> let foo = show (1, (2, "hello", 3))
>>> pPrintStringOpt CheckColorTty defaultOutputOptionsNoColor foo
( 1
,
    ( 2
    , "hello"
    , 3
    )
)

pHPrintStringOpt :: MonadIO m => CheckColorTty -> OutputOptions -> Handle -> String -> m () Source #

Similar to pPrintStringOpt, but take a Handle to determine where to print to.

>>> let foo = show (1, (2, "hello", 3))
>>> pHPrintStringOpt CheckColorTty defaultOutputOptionsNoColor stdout foo
( 1
,
    ( 2
    , "hello"
    , 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
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 -> Type #

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-3.2.2.0-93AickV4ocl4iiUojq5JD3" 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)) :*: S1 (MetaSel (Just "outputOptionsEscapeNonPrintable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

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.

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 Handle is a TTY device. If the output Handle is a TTY device, determine whether to print in color based on outputOptionsColorOptions. If not, then set outputOptionsColorOptions to Nothing so the output does not get colorized.

NoCheckColorTty

Don't check if the output Handle is a TTY device. Determine whether to colorize the output based solely on the value of outputOptionsColorOptions.

Instances
Eq CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Show CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Generic CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

Associated Types

type Rep CheckColorTty :: Type -> Type #

type Rep CheckColorTty Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.OutputPrinter

type Rep CheckColorTty = D1 (MetaData "CheckColorTty" "Text.Pretty.Simple.Internal.OutputPrinter" "pretty-simple-3.2.2.0-93AickV4ocl4iiUojq5JD3" False) (C1 (MetaCons "CheckColorTty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoCheckColorTty" PrefixI False) (U1 :: Type -> Type))

ColorOptions

Additional settings for color options can be found in Text.Pretty.Simple.Internal.Color.

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.

Simple Haskell data type

>>> data Foo a = Foo a String Char deriving Show
>>> pPrint $ Foo 3 "hello" 'a'
Foo 3 "hello" 'a'

List

>>> pPrint $ [1,2,3]
[ 1
, 2
, 3
]

Slightly more complicated list

>>> pPrint $ [ Foo [ (), () ] "hello" 'b' ]
[ Foo
    [ ()
    , ()
    ] "hello" 'b'
]
>>> pPrint $ [ Foo [ "bar", "baz" ] "hello" 'a', Foo [] "bye" 'b' ]
[ Foo
    [ "bar"
    , "baz"
    ] "hello" 'a'
, Foo [] "bye" 'b'
]

Record

>>> :{
data Bar b = Bar
  { barInt :: Int
  , barA :: b
  , barList :: [Foo Double]
  } deriving Show
:}
>>> pPrint $ Bar 1 [10, 11] [Foo 1.1 "" 'a', Foo 2.2 "hello" 'b']
Bar
    { barInt = 1
    , barA =
        [ 10
        , 11
        ]
    , barList =
        [ Foo 1.1 "" 'a'
        , Foo 2.2 "hello" 'b'
        ]
    }

Newtype

>>> newtype Baz = Baz { unBaz :: [String] } deriving Show
>>> pPrint $ Baz ["hello", "bye"]
Baz
    { unBaz =
        [ "hello"
        , "bye"
        ]
    }

Newline Rules

>>> data Foo = A | B Foo | C [Foo] [Foo] deriving Show
>>> pPrint $ B ( B A )
B ( B A )
>>> pPrint $ B ( B ( B A ) )
B
    ( B ( B A ) )
>>> pPrint $ B ( B ( B ( B A ) ) )
B
    ( B
        ( B ( B A ) )
    )
>>> pPrint $ B ( C [A, A] [B A, B (B (B A))] )
B
    ( C
        [ A
        , A
        ]
        [ B A
        , B
            ( B ( B A ) )
        ]
    )

Laziness

>>> take 100 . unpack . pShowNoColor $ [1..]
"[ 1\n, 2\n, 3\n, 4\n, 5\n, 6\n, 7\n, 8\n, 9\n, 10\n, 11\n, 12\n, 13\n, 14\n, 15\n, 16\n, 17\n, 18\n, 19\n, 20\n, 21\n, 22"

Unicode

>>> pPrint $ Baz ["猫", "犬", "ヤギ"]
Baz
    { unBaz =
        [ "猫"
        , "犬"
        , "ヤギ"
        ]
    }

Other

Making sure the spacing after a string is correct.

>>> data Foo = Foo String Int deriving Show
>>> pPrint $ Foo "bar" 0
Foo "bar" 0

Non-printable characters will get escaped.

>>> pPrint "this string has non-printable characters: \x8 and \x9"
"this string has non-printable characters: \x8 and \x9"