pretty-show-1.10: Tools for working with derived `Show` instances and generic inspection of values.

Copyright(c) Iavor S. Diatchki 2009
LicenseMIT
Maintaineriavor.diatchki@gmail.com
Stabilityprovisional
PortabilityHaskell 98
Safe HaskellSafe
LanguageHaskell98

Text.Show.Pretty

Contents

Description

Functions for human-readable derived Show instances.

Synopsis

Generic representation of values

data Value Source #

Generic Haskell values. NaN and Infinity are represented as constructors. The Value in the literals is the text for the literals "as is".

A chain of infix constructors means that they appeared in the input string without parentheses, i.e

1 :+: 2 :*: 3 is represented with InfixCons 1 [(":+:",2),(":*:",3)], whereas

1 :+: (2 :*: 3) is represented with InfixCons 1 [(":+:",InfixCons 2 [(":*:",3)])].

Constructors

Con Name [Value]

Data constructor

InfixCons Value [(Name, Value)]

Infix data constructor chain

Rec Name [(Name, Value)]

Record value

Tuple [Value]

Tuple

List [Value]

List

Neg Value

Negated value

Ratio Value Value

Rational

Integer String

Non-negative integer

Float String

Non-negative floating num.

Char String

Character

String String

String

Date String

01-02-2003

Time String

08:30:21

Quote String
time|2003-02-01T08:30:21Z|
Instances
Eq Value Source # 
Instance details

Defined in Text.Show.Value

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value Source # 
Instance details

Defined in Text.Show.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

type Name = String Source #

A name.

valToStr :: Value -> String Source #

Pretty print a generic value. Our intention is that the result is equivalent to the Show instance for the original value, except possibly easier to understand by a human.

valToDoc :: Value -> Doc Source #

Pretty print a generic value. Our intention is that the result is equivalent to the Show instance for the original value, except possibly easier to understand by a human.

valToHtmlPage :: HtmlOpts -> Value -> String Source #

Make an Html page representing the given value.

Values using the Show class

reify :: Show a => a -> Maybe Value Source #

ppDoc :: Show a => a -> Doc Source #

Try to show a value, prettily. If we do not understand the value, then we just use its standard Show instance.

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

Convert a generic value into a pretty Value, if possible.

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

Pretty print a generic value to stdout. This is particularly useful in the GHCi interactive environment.

Working with listlike ("foldable") collections

ppDocList :: (Foldable f, Show a) => f a -> Doc Source #

Pretty print something that may be converted to a list as a list. Each entry is on a separate line, which means that we don't do clever pretty printing, and so this works well for large strucutures.

ppShowList :: (Foldable f, Show a) => f a -> String Source #

Pretty print something that may be converted to a list as a list. Each entry is on a separate line, which means that we don't do clever pretty printing, and so this works well for large strucutures.

pPrintList :: (Foldable f, Show a) => f a -> IO () Source #

Pretty print something that may be converted to a list as a list. Each entry is on a separate line, which means that we don't do clever pretty printing, and so this works well for large strucutures.

Values using the PrettyVal class

dumpDoc :: PrettyVal a => a -> Doc Source #

Render a value in the PrettyVal class to a Doc. The benefit of this function is that PrettyVal instances may be derived automatically using generics.

dumpStr :: PrettyVal a => a -> String Source #

Render a value in the PrettyVal class to a Value. The benefit of this function is that PrettyVal instances may be derived automatically using generics.

dumpIO :: PrettyVal a => a -> IO () Source #

Render a value using the PrettyVal class and show it to standard out.

class PrettyVal a where Source #

A class for types that may be reified into a value. Instances of this class may be derived automatically, for datatypes that support Generics.

Minimal complete definition

Nothing

Methods

prettyVal :: a -> Value Source #

prettyVal :: (GDump (Rep a), Generic a) => a -> Value Source #

Instances
PrettyVal Bool Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Char Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Double Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Float Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Int Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Int8 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Int16 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Int32 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Int64 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Integer Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Ordering Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Word8 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Word16 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Word32 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Word64 Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal Text Source # 
Instance details

Defined in Text.Show.PrettyVal

PrettyVal a => PrettyVal [a] Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: [a] -> Value Source #

listValue :: [[a]] -> Value

PrettyVal a => PrettyVal (Maybe a) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: Maybe a -> Value Source #

listValue :: [Maybe a] -> Value

(PrettyVal a, Integral a) => PrettyVal (Ratio a) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: Ratio a -> Value Source #

listValue :: [Ratio a] -> Value

HasResolution p => PrettyVal (Fixed p) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: Fixed p -> Value Source #

listValue :: [Fixed p] -> Value

(PrettyVal a, PrettyVal b) => PrettyVal (Either a b) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: Either a b -> Value Source #

listValue :: [Either a b] -> Value

(PrettyVal a1, PrettyVal a2) => PrettyVal (a1, a2) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: (a1, a2) -> Value Source #

listValue :: [(a1, a2)] -> Value

(PrettyVal a1, PrettyVal a2, PrettyVal a3) => PrettyVal (a1, a2, a3) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: (a1, a2, a3) -> Value Source #

listValue :: [(a1, a2, a3)] -> Value

(PrettyVal a1, PrettyVal a2, PrettyVal a3, PrettyVal a4) => PrettyVal (a1, a2, a3, a4) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: (a1, a2, a3, a4) -> Value Source #

listValue :: [(a1, a2, a3, a4)] -> Value

(PrettyVal a1, PrettyVal a2, PrettyVal a3, PrettyVal a4, PrettyVal a5) => PrettyVal (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: (a1, a2, a3, a4, a5) -> Value Source #

listValue :: [(a1, a2, a3, a4, a5)] -> Value

(PrettyVal a1, PrettyVal a2, PrettyVal a3, PrettyVal a4, PrettyVal a5, PrettyVal a6) => PrettyVal (a1, a2, a3, a4, a5, a6) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: (a1, a2, a3, a4, a5, a6) -> Value Source #

listValue :: [(a1, a2, a3, a4, a5, a6)] -> Value

(PrettyVal a1, PrettyVal a2, PrettyVal a3, PrettyVal a4, PrettyVal a5, PrettyVal a6, PrettyVal a7) => PrettyVal (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Text.Show.PrettyVal

Methods

prettyVal :: (a1, a2, a3, a4, a5, a6, a7) -> Value Source #

listValue :: [(a1, a2, a3, a4, a5, a6, a7)] -> Value

Rendering values to Html

valToHtml :: HtmlOpts -> Value -> Html Source #

Convert a value into an Html fragment.

data HtmlOpts Source #

Options on how to generate Html (more to come).

Constructors

HtmlOpts 

Fields

  • dataDir :: FilePath

    Path for extra files. If empty, we look in directory style, relative to document.

  • wideListWidth :: Int

    Max. number of columns in wide lists.

Instances
Show HtmlOpts Source # 
Instance details

Defined in Text.Show.Html

defaultHtmlOpts :: HtmlOpts Source #

Default options.

htmlPage :: HtmlOpts -> Html -> String Source #

Wrap an Html fragment to make an Html page.

newtype Html Source #

Constructors

Html 

Fields

Get location of data files

Preprocessing of values

data PreProc a Source #

This type is used to allow pre-processing of values before showing them.

Constructors

PreProc (Value -> Value) a 
Instances
Show a => Show (PreProc a) Source # 
Instance details

Defined in Text.Show.Pretty

Methods

showsPrec :: Int -> PreProc a -> ShowS #

show :: PreProc a -> String #

showList :: [PreProc a] -> ShowS #

ppHide :: (Name -> Bool) -> a -> PreProc a Source #

Hide the given constructors when showing a value.

ppHideNested :: (Name -> Bool) -> a -> PreProc a Source #

Hide the given constructors when showing a value. In addition, hide values if all of their children were hidden.

hideCon :: Bool -> (Name -> Bool) -> Value -> Value Source #

Hide constrcutros matching the given predicate. If the hidden value is in a record, we also hide the corresponding record field.

If the boolean flag is true, then we also hide constructors all of whose fields were hidden.

Deprecated

ppValue :: Value -> Doc Source #

Deprecated: Please use valToDoc instead.