pretty-simple-0.3.0.0: Simple pretty printer for any datatype 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

 

Synopsis

Output With Color

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

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

Output With NO Color

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

Output With Output Options

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

data OutputOptions Source #

Data-type wrapping up all the options available when rendering the list of Outputs.

Constructors

OutputOptions 

Fields

  • _indentAmount :: Int

    Number of spaces to use when indenting. It should probably be either 2 or 4.

  • _useColor :: UseColor

    Whether or not to use ansi escape sequences to print colors.

Instances

Eq OutputOptions Source # 
Data OutputOptions Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OutputOptions -> c OutputOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OutputOptions #

toConstr :: OutputOptions -> Constr #

dataTypeOf :: OutputOptions -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OutputOptions) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OutputOptions) #

gmapT :: (forall b. Data b => b -> b) -> OutputOptions -> OutputOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OutputOptions -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OutputOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> OutputOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OutputOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OutputOptions -> m OutputOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputOptions -> m OutputOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputOptions -> m OutputOptions #

Read OutputOptions Source # 
Show OutputOptions Source # 
Generic OutputOptions Source # 

Associated Types

type Rep OutputOptions :: * -> * #

type Rep OutputOptions Source # 
type Rep OutputOptions = D1 (MetaData "OutputOptions" "Text.Pretty.Simple.Internal.OutputPrinter" "pretty-simple-0.3.0.0-3wchzkAsRi413q23oEpzwT" False) (C1 (MetaCons "OutputOptions" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_indentAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "_useColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UseColor))))

data UseColor Source #

UseColor describes whether or not we want to use color when printing the Output list.

Constructors

NoColor 
UseColor 

Instances

Eq UseColor Source # 
Data UseColor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UseColor -> c UseColor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UseColor #

toConstr :: UseColor -> Constr #

dataTypeOf :: UseColor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UseColor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UseColor) #

gmapT :: (forall b. Data b => b -> b) -> UseColor -> UseColor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UseColor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UseColor -> r #

gmapQ :: (forall d. Data d => d -> u) -> UseColor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UseColor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UseColor -> m UseColor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UseColor -> m UseColor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UseColor -> m UseColor #

Read UseColor Source # 
Show UseColor Source # 
Generic UseColor Source # 

Associated Types

type Rep UseColor :: * -> * #

Methods

from :: UseColor -> Rep UseColor x #

to :: Rep UseColor x -> UseColor #

type Rep UseColor Source # 
type Rep UseColor = D1 (MetaData "UseColor" "Text.Pretty.Simple.Internal.OutputPrinter" "pretty-simple-0.3.0.0-3wchzkAsRi413q23oEpzwT" False) ((:+:) (C1 (MetaCons "NoColor" PrefixI False) U1) (C1 (MetaCons "UseColor" PrefixI False) U1))

defaultOutputOptions :: OutputOptions Source #

Default values for OutputOptions. _indentAmount defaults to 4, and _useColor defaults to UseColor.

Examples

Simple Haskell datatype:

>>> data Foo a = Foo a String deriving Show
>>> pPrintNoColor $ Foo 3 "hello"
Foo 3 "hello"

Lists:

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

Slightly more complicated lists:

>>> 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"
        ]
    }