pretty-types-0.1.0.2: A small pretty printing DSL for complex types.

Safe HaskellNone
LanguageHaskell2010

Data.Type.Pretty

Contents

Description

Type Pretty Printing

Printing Custom Types

The main usecase is of course printing one own complex types.

Convert a custom type to the PrettyType eDSL, then render it using ptShow.

ToPretty is the hooks for pretty type printing custom types, while showPretty renders a type with a ToPretty instance.

ToPretty is an open type family, that maps types to PrettyTypes. One way to create PrettyType documents is to define instances for your types, which construct a type of kind PrettyType using the promoted constructors of PrettyType.

Use the type aliases to get rid of unticked or even ticked promoteds.

Example

This example shows howto render this table:

+-------+-----+------------+
|  col 1|col 2|       col 3|
+-------+-----+------------+
|   2423|  451|       21234|
| 242322|   42|         n/a|
|      0| 4351|      623562|
|   4351|  n/a|         n/a|
|      0| 4351|      623562|
+-------+-----+------------+

Assume a custom type for tables calles MyTable.

Rendering this table:

type TestTable =
  'MyTable         '[MyCol "col 1" 7, MyCol "col 2" 5, MyCol "col 3" 12]
          '[ MyRow '[2423           ,451             ,21234]
           , MyRow '[242322         ,42]
           , MyRow '[0              ,4351            ,623562]
           , MyRow '[4351]
           , MyRow '[0              ,4351            ,623562]
           ]

Using this function:

prettyTestTable :: String
prettyTestTable = showPretty (Proxy :: Proxy TestTable)

These are the data types. Note that only numbers can be stored in MyTable.

-- | A type with a list of columns and rows.
data MyTable = MyTable [Type] [Type]

-- | A row of a table, with a list of values, one each for every column.
data MyRow :: [Nat] -> Type

-- | The column of a table. It has a width and a column title.
data MyCol :: Symbol -> Nat -> Type

Here's the top-level ToPretty instance:

type instance ToPretty ('MyTable cols rows) =
           PrettyManyIn (PutStr "+") (RowSepLine cols)
      <$$> PrettyManyIn (PutStr "|") (TableHeading cols)
      <$$> PrettyManyIn (PutStr "+") (RowSepLine cols)
      <$$> PrettyHigh   (TableRows cols rows)
      <$$> PrettyManyIn (PutStr "+") (RowSepLine cols)

It delegates to these:

type family
  TableHeading (cols :: [Type]) :: [PrettyType] where
  TableHeading '[]                      = '[]
  TableHeading (MyCol title width ': r) = PutStrW width title  ': TableHeading  r

type family
   RowSepLine (cols :: [Type]) :: [PrettyType] where
   RowSepLine '[] = '[]
   RowSepLine (MyCol title width ': r) =
     PrettyOften width (PutStr "-") ': RowSepLine  r

type family
  TableRows (cols :: [Type]) (rows :: [Type]) :: [PrettyType] where
  TableRows cols '[] = '[]
  TableRows cols (MyRow cells ': rest ) =
    PrettyManyIn (PutStr "|") (TableCells cols cells) ': TableRows cols rest

type family
  TableCells (cols :: [Type]) (cells :: [Nat]) :: [PrettyType] where
  TableCells '[] cells = '[]
  TableCells (MyCol title width ': cols) (value ': cells) =
    PutNatW width value ':  TableCells cols cells
  TableCells (MyCol title width ': cols) '[] =
    PutStrW width "n/a" ':  TableCells cols '[]

Synopsis

Printing Custom Types

showPretty Source #

Arguments

:: PrettyTypeShow (ToPretty t) 
=> proxy t

A proxy to the type to print. A ToPretty instance for t must exists.

-> String 

Pretty print a type for which a ToPretty instance was defined, that converts the type to a PrettyType. If you want to roll your own converter for your type to PrettyType, just do that and call ptShow directly.

type family ToPretty (a :: k) :: PrettyType Source #

Write an instance of this for converting your type (preferrable of your kind also) to a promoted PrettyType. NOTE: It might be helpful to turn on UndecidableInstances and use the type like PutStr aliases below.

Building Pretty Type Documents

type PutStrW width str = PrettySymbol (PrettyPadded width) (PrettyPrecision width) str Source #

A PrettyType for a string with the exact given width.

type PutStrLn str = PutStr str <++> PutStr "\n" Source #

A PrettyType for a string with a newline character at the end.

type PutNatW width x = PrettyNat (PrettyPadded width) PrettyPrecise PrettyDec x Source #

A PrettyType for a number with a width.

type (<++>) l r = PrettySeperated PrettyEmpty l r infixl 6 Source #

Concatenate two PrettyType.

type (<+>) l r = PrettySeperated PrettySpace l r infixl 5 Source #

Concatenate two PrettyType using a PrettySpace.

type (<$$>) l r = PrettySeperated PrettyNewline l r infixl 4 Source #

Concatenate two PrettyType using a PrettyNewline.

type PrettyParens doc = PrettySurrounded (PutStr "(") (PutStr ")") doc Source #

Surround a pretty with parens

type PrettySurrounded open close doc = (open <++> doc) <++> close Source #

Surround a pretty with some pretties

type PrettyWide docs = PrettyMany PrettySpace docs Source #

Combine a (type level) list of PrettyTypes next to each other using PrettySpace

type PrettyHigh docs = PrettyMany PrettyNewline docs Source #

Combine a (type level) list of PrettyTypes below each other using PrettyNewline

type PrettyManyIn sep docs = PrettySurrounded sep sep (PrettyMany sep docs) Source #

A combination of PrettySpace and PrettyMany, e.g.:

>>> ptShow (Proxy :: Proxy (PrettyManyIn (PutStr "|") '[PutStr "a", PutStr "b"]))
"|a|b|"

type family PrettyMany (sep :: PrettyType) (docs :: [PrettyType]) :: PrettyType where ... Source #

Combine a (type level) list of PrettyTypes seperated by a seperation element.

Equations

PrettyMany sep '[] = PrettyEmpty 
PrettyMany sep '[singleOne] = singleOne 
PrettyMany sep (next ': rest) = (next <++> sep) <++> PrettyMany sep rest 

type family PrettyOften (n :: Nat) (doc :: PrettyType) :: PrettyType where ... Source #

Repeat a PrettyType n-times and append the copies.

Equations

PrettyOften 0 doc = PrettyEmpty 
PrettyOften n doc = doc <++> PrettyOften (n - 1) doc 

type PutHex x = PrettyNat PrettyUnpadded PrettyPrecise PrettyHex x Source #

Create PrettyType from a Nat formatted as hex number using lower-case letters for the hex digits.

type PutHex8 x = PrettyNat PrettyUnpadded (PrettyPrecision 2) PrettyHex x Source #

Create PrettyType from a Nat formatted as 8 bit hex number using lower-case letters for the hex digits.

type PutHex16 x = PrettyNat PrettyUnpadded (PrettyPrecision 4) PrettyHex x Source #

Create PrettyType from a Nat formatted as 16 bit hex number using lower-case letters for the hex digits.

type PutHex32 x = PrettyNat PrettyUnpadded (PrettyPrecision 8) PrettyHex x Source #

Create PrettyType from a Nat formatted as 32 bit hex number using lower-case letters for the hex digits.

type PutHex64 x = PrettyNat PrettyUnpadded (PrettyPrecision 16) PrettyHex x Source #

Create PrettyType from a Nat formatted as 64 bit hex number using lower-case letters for the hex digits.

type PutHeX x = PrettyNat PrettyUnpadded PrettyPrecise PrettyHexU x Source #

Create PrettyType from a Nat formatted as hex number using lower-case letters for the hex digits.

type PutHeX8 x = PrettyNat PrettyUnpadded (PrettyPrecision 2) PrettyHexU x Source #

Create PrettyType from a Nat formatted as 8 bit hex number using uppercase letters for the hex digits.

type PutHeX16 x = PrettyNat PrettyUnpadded (PrettyPrecision 4) PrettyHexU x Source #

Create PrettyType from a Nat formatted as 16 bit hex number using uppercase letters for the hex digits.

type PutHeX32 x = PrettyNat PrettyUnpadded (PrettyPrecision 8) PrettyHexU x Source #

Create PrettyType from a Nat formatted as 32 bit hex number using uppercase letters for the hex digits.

type PutHeX64 x = PrettyNat PrettyUnpadded (PrettyPrecision 16) PrettyHexU x Source #

Create PrettyType from a Nat formatted as 64 bit hex number using uppercase letters for the hex digits.

type PutBits x = PrettyNat PrettyUnpadded PrettyPrecise PrettyBit x Source #

Create PrettyType from a Nat formatted as bit representation,

>>> ptShow (Proxy :: Proxy (PutBits 5))
"101"

type PutBits8 x = PrettyNat PrettyUnpadded (PrettyPrecision 8) PrettyBit x Source #

Create PrettyType from a Nat formatted as 8-bit bit representation,

>>> ptShow (Proxy :: Proxy (PutBits8 5))
"00000101"

type PutBits16 x = PrettyNat PrettyUnpadded (PrettyPrecision 16) PrettyBit x Source #

Create PrettyType from a Nat formatted as 16-bit bit representation,

>>> ptShow (Proxy :: Proxy (PutBits16 5))
"00000000000000101"

type PutBits32 x = PrettyNat PrettyUnpadded (PrettyPrecision 32) PrettyBit x Source #

Create PrettyType from a Nat formatted as 32-bit bit representation,

>>> ptShow (Proxy :: Proxy (PutBits32 5))
"00000000000000000000000000000000101"

type PutBits64 x = PrettyNat PrettyUnpadded (PrettyPrecision 64) PrettyBit x Source #

Create PrettyType from a Nat formatted as 64-bit bit representation,

>>> ptShow (Proxy :: Proxy (PutBits64 5))
"00000000000000000000000000000000000000000000000000000000000000000000101"

data PrettyType where Source #

Combinators for type documents.

The basis for pretty printing is this eDSL. It is rendered via the PrettyTypeShow instances for its promoted constructors.

Only the promoted constructors are used, only they have instances for that class.

data PrettyPadded where Source #

Constructors

PrettyUnpadded :: PrettyPadded

No minimum or fixed width

PrettyPadded :: Nat -> PrettyPadded

Pad a PrettySymbol or PrettyNat with spaces or zeros. NOTE PrettyNats will never be shorter than the minimum number of digits, regardless of this padding.

Instances

PrintfArgModifier PrettyPadded PrettyUnpadded Source #

Translation of PrettyUnpadded to an empty modifier string

KnownNat p => PrintfArgModifier PrettyPadded (PrettyPadded p) Source #

Translation of PrettyPadded to a string with the numeric padding value.

data PrettyPrecision where Source #

The precision for PrettySymbol and PrettyNat.

Constructors

PrettyPrecise :: PrettyPrecision

No minimum precision.

PrettyPrecision :: Nat -> PrettyPrecision

Precision, for Symbols the maximum width, for Nats the minimum digits. NOTEPrettyNats will never be shorter than the minimum number of digits, wheres PrettySymbols will be truncated if they are longer than the precision.

Instances

PrintfArgModifier PrettyPrecision PrettyPrecise Source #

Translation of PrettyPrecise to an empty modifier string

KnownNat p => PrintfArgModifier PrettyPrecision (PrettyPrecision p) Source #

Translation of PrettyPadded to a string with the numeric precision value, prependen by a dot ".".

data PrettyNatFormat Source #

PrettyNat formatting options.

Constructors

PrettyHex

Hexa decimal rendering:

>>> ptShow (Proxy::Proxy (PrettyNat PrettyUnpadded PrettyPrecise PrettyHex 51966))
"cafe"
PrettyHexU

Hexa decimal rendering (upper case):

>>> ptShow (Proxy::Proxy (PrettyNat PrettyUnpadded PrettyPrecise PrettyHexU 51966))
"CAFE"
PrettyDec

Decimal rendering:

>>> ptShow (Proxy::Proxy (PrettyNat PrettyUnpadded PrettyPrecise PrettyHexU 51966))
"51966"
PrettyBit

Binary rendering:

>>> ptShow (Proxy::Proxy (PrettyNat PrettyUnpadded PrettyPrecise PrettyHexU 51966))
"1100101011111110"

Instances

PrintfArgModifier PrettyNatFormat PrettyHex Source #

Translation of PrettyHex to printf format character: "x"

PrintfArgModifier PrettyNatFormat PrettyHexU Source #

Translation of PrettyHexU to printf format character: X

PrintfArgModifier PrettyNatFormat PrettyDec Source #

Translation of PrettyDec to printf format character: "d"

PrintfArgModifier PrettyNatFormat PrettyBit Source #

Translation of PrettyBit to printf format character: "b"

Low-Level Rendering

class PrettyTypeShow p where Source #

In order to actually print anything from the promoted constructors of PrettyTypeShow, a type class as common interface is required.

Minimal complete definition

ptShow

Methods

ptShow :: proxy p -> String Source #

Instances

PrettyTypeShow PrettyEmpty Source #

Print nothing.

Methods

ptShow :: proxy PrettyEmpty -> String Source #

PrettyTypeShow PrettySpace Source #

Print a single space character.

Methods

ptShow :: proxy PrettySpace -> String Source #

PrettyTypeShow PrettyNewline Source #

Print a single newline character.

Methods

ptShow :: proxy PrettyNewline -> String Source #

(KnownSymbol t, PrintfArgModifier PrettyPadded pad, PrintfArgModifier PrettyPrecision prec) => PrettyTypeShow (PrettySymbol pad prec t) Source #

Print a Symbol using the printf and the given format parameters.

Methods

ptShow :: proxy (PrettySymbol pad prec t) -> String Source #

(PrettyTypeShow sep, PrettyTypeShow l, PrettyTypeShow r) => PrettyTypeShow (PrettySeperated sep l r) Source #

Concatenate two PrettyTypes. If one of them is empty print the other without any seperation character.

Methods

ptShow :: proxy (PrettySeperated sep l r) -> String Source #

(KnownNat x, PrintfArgModifier PrettyNatFormat fmt, PrintfArgModifier PrettyPadded pad, PrintfArgModifier PrettyPrecision prec) => PrettyTypeShow (PrettyNat pad prec fmt x) Source #

Print a Nat using the printf and the given format parameters.

Methods

ptShow :: proxy (PrettyNat pad prec fmt x) -> String Source #

class PrintfArgModifier a where Source #

Internal printf format generation. Used internally by PrettyTypeShow instances to generate the format string piece by piece with the values for the instances of e.g. PrettyPrecise, PrettyNatFormat, or PrettyEmpty.

Minimal complete definition

toPrintfArgModifier

Methods

toPrintfArgModifier :: p a -> String Source #

Generate a piece of a printf format string from a proxy for a type.

Instances

PrintfArgModifier PrettyNatFormat PrettyHex Source #

Translation of PrettyHex to printf format character: "x"

PrintfArgModifier PrettyNatFormat PrettyHexU Source #

Translation of PrettyHexU to printf format character: X

PrintfArgModifier PrettyNatFormat PrettyDec Source #

Translation of PrettyDec to printf format character: "d"

PrintfArgModifier PrettyNatFormat PrettyBit Source #

Translation of PrettyBit to printf format character: "b"

PrintfArgModifier PrettyPrecision PrettyPrecise Source #

Translation of PrettyPrecise to an empty modifier string

PrintfArgModifier PrettyPadded PrettyUnpadded Source #

Translation of PrettyUnpadded to an empty modifier string

KnownNat p => PrintfArgModifier PrettyPrecision (PrettyPrecision p) Source #

Translation of PrettyPadded to a string with the numeric precision value, prependen by a dot ".".

KnownNat p => PrintfArgModifier PrettyPadded (PrettyPadded p) Source #

Translation of PrettyPadded to a string with the numeric padding value.