model-0.3: Derive a model of a data type using Generics

Safe HaskellSafe
LanguageHaskell2010

Data.Model.Pretty

Contents

Description

Pretty instances for the model types

Synopsis

Documentation

data CompactPretty a Source #

Compact representation: a value enveloped in CompactPretty will have only its first lines displayed

Constructors

CompactPretty a 

Utilities

dotted :: [String] -> Doc Source #

Intercalate with a dot

spacedP :: Pretty a => [a] -> Doc Source #

Separate with a space

vspacedP :: Pretty a => [a] -> Doc Source #

Separate with a new line

varP :: Integral n => n -> Doc Source #

Convert a variable number (0,1,..) to a name (a,b,..)

Re-exports

class Pretty a where #

Pretty printing class. The precedence level is used in a similar way as in the Show class. Minimal complete definition is either pPrintPrec or pPrint.

Minimal complete definition

pPrintPrec | pPrint

Methods

pPrintPrec :: PrettyLevel -> Rational -> a -> Doc #

pPrint :: a -> Doc #

pPrintList :: PrettyLevel -> [a] -> Doc #

Instances

Pretty Bool 
Pretty Char 
Pretty Double 
Pretty Float 
Pretty Int 
Pretty Integer 
Pretty Ordering 
Pretty () 

Methods

pPrintPrec :: PrettyLevel -> Rational -> () -> Doc #

pPrint :: () -> Doc #

pPrintList :: PrettyLevel -> [()] -> Doc #

Pretty a => Pretty [a] 

Methods

pPrintPrec :: PrettyLevel -> Rational -> [a] -> Doc #

pPrint :: [a] -> Doc #

pPrintList :: PrettyLevel -> [[a]] -> Doc #

Pretty a => Pretty (Maybe a) 
Pretty a => Pretty (CompactPretty a) # 
(Pretty a, Pretty b) => Pretty (Either a b) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> Either a b -> Doc #

pPrint :: Either a b -> Doc #

pPrintList :: PrettyLevel -> [Either a b] -> Doc #

(Pretty a, Pretty b) => Pretty (a, b) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b) -> Doc #

pPrint :: (a, b) -> Doc #

pPrintList :: PrettyLevel -> [(a, b)] -> Doc #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c) -> Doc #

pPrint :: (a, b, c) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d) -> Doc #

pPrint :: (a, b, c, d) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e) -> Doc #

pPrint :: (a, b, c, d, e) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f) -> Doc #

pPrint :: (a, b, c, d, e, f) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g) -> Doc #

pPrint :: (a, b, c, d, e, f, g) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => Pretty (a, b, c, d, e, f, g, h) 

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g, h) -> Doc #

pPrint :: (a, b, c, d, e, f, g, h) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g, h)] -> Doc #

prettyShow :: Pretty a => a -> String #

Pretty print a value with the prettyNormal level.

Orphan instances

Pretty Doc Source # 
Pretty Name Source # 
Pretty QualName Source # 
Pretty n => Pretty (TypeRef n) Source # 
Pretty r => Pretty (TypeN r) Source # 
Pretty r => Pretty (Type r) Source # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> Type r -> Doc #

pPrint :: Type r -> Doc #

pPrintList :: PrettyLevel -> [Type r] -> Doc #

(Pretty name, Pretty ref) => Pretty (ConTree name ref) Source # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> ConTree name ref -> Doc #

pPrint :: ConTree name ref -> Doc #

pPrintList :: PrettyLevel -> [ConTree name ref] -> Doc #

(Pretty n, Pretty cn, Pretty r) => Pretty (ADT n cn r) Source # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> ADT n cn r -> Doc #

pPrint :: ADT n cn r -> Doc #

pPrintList :: PrettyLevel -> [ADT n cn r] -> Doc #

(Functor t, Pretty (t Name), Pretty exRef, Ord exRef, Show exRef, StringLike adtName, StringLike consName, StringLike iref) => Pretty (TypeModel adtName consName (t iref) exRef) Source # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> TypeModel adtName consName (t iref) exRef -> Doc #

pPrint :: TypeModel adtName consName (t iref) exRef -> Doc #

pPrintList :: PrettyLevel -> [TypeModel adtName consName (t iref) exRef] -> Doc #