| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Type.Pretty
Contents
Description
Type Pretty Printing
Printing Custom Types
The main usecase of this library is rendering one's own complex types to
pretty String values, e.g. for debugging and tracing purposes.
One way to create PrettyType documents is to define ToPretty instances
for your types by combining the promoted constructors of PrettyType.
If UndecidableInstances isn't holding you back, use the type aliases like
PutStr, PutNat, PrettyInfix, etc in these instance definitions.
ToPretty is an open type family, that converts a custom type to a
PrettyType.
showPretty eventually crafts a String value from a proxy to the custom
type.
It might be helpful to overcome egoistic needs for guaranteed compiler
termination (i.e. allowing UndecidableInstances) in order to be able to use
type aliases like PutStr, PutNat, etc.
Example
Let's start with the output:
+-------+-----+------------+ | col 1|col 2| col 3| +-------+-----+------------+ | 2423| 451| 21234| | 242322| 42| n/a| | 0| 4351| 623562| | 4351| n/a| n/a| | 0| 4351| 623562| +-------+-----+------------+
... of 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)
...from these data types:
-- | A type with a list of columns and rows. data MyTable = MyTable [Type] [Type] -- | A row of a table, with a list of numbers, 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
...converted to PrettyType using this ToPretty instance:
type instanceToPretty('MyTable cols rows) =PrettyManyIn(PutStr"+") (RowSepLine cols)<$$>PrettyManyIn(PutStr"|") (TableHeading cols)<$$>PrettyManyIn(PutStr"+") (RowSepLine cols)<$$>PrettyHigh(TableRows cols rows)<$$>PrettyManyIn(PutStr"+") (RowSepLine cols) type family TableHeading (cols :: [Type]) :: [PrettyType] where TableHeading '[] = '[] TableHeading (MyCol title width ': r) =PutStrWwidth title ': TableHeading r type family RowSepLine (cols :: [Type]) :: [PrettyType] where RowSepLine '[] = '[] RowSepLine (MyCol title width ': r) =PrettyOftenwidth (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) =PutNatWwidth value ': TableCells cols cells TableCells (MyCol title width ': cols) '[] =PutStrWwidth "n/a" ': TableCells cols '[]
- showPretty :: forall proxy t. PrettyTypeShow (ToPretty t) => proxy t -> String
- type family ToPretty (a :: k) :: PrettyType
- type PutStr str = PrettySymbol PrettyUnpadded PrettyPrecise str
- type PutStrW width str = PrettySymbol (PrettyPadded width) (PrettyPrecision width) str
- type PutStrLn str = PutStr str <++> PutStr "\n"
- type PutNat x = PrettyNat PrettyUnpadded PrettyPrecise PrettyDec x
- type PutNatW width x = PrettyNat (PrettyPadded width) PrettyPrecise PrettyDec x
- type PutHex x = PrettyNat PrettyUnpadded PrettyPrecise PrettyHex x
- type PutHex8 x = PrettyNat PrettyUnpadded (PrettyPrecision 2) PrettyHex x
- type PutHex16 x = PrettyNat PrettyUnpadded (PrettyPrecision 4) PrettyHex x
- type PutHex32 x = PrettyNat PrettyUnpadded (PrettyPrecision 8) PrettyHex x
- type PutHex64 x = PrettyNat PrettyUnpadded (PrettyPrecision 16) PrettyHex x
- type PutHeX x = PrettyNat PrettyUnpadded PrettyPrecise PrettyHexU x
- type PutHeX8 x = PrettyNat PrettyUnpadded (PrettyPrecision 2) PrettyHexU x
- type PutHeX16 x = PrettyNat PrettyUnpadded (PrettyPrecision 4) PrettyHexU x
- type PutHeX32 x = PrettyNat PrettyUnpadded (PrettyPrecision 8) PrettyHexU x
- type PutHeX64 x = PrettyNat PrettyUnpadded (PrettyPrecision 16) PrettyHexU x
- type PutBits x = PrettyNat PrettyUnpadded PrettyPrecise PrettyBit x
- type PutBits8 x = PrettyNat PrettyUnpadded (PrettyPrecision 8) PrettyBit x
- type PutBits16 x = PrettyNat PrettyUnpadded (PrettyPrecision 16) PrettyBit x
- type PutBits32 x = PrettyNat PrettyUnpadded (PrettyPrecision 32) PrettyBit x
- type PutBits64 x = PrettyNat PrettyUnpadded (PrettyPrecision 64) PrettyBit x
- type (<:>) label body = PrettySuffix (PutStr ":") (PutStr label) <+> body
- type (<:$$>) label body = PrettySuffix (PutStr ":") (PutStr label) <$$> body
- type (<:$$-->) label body = PrettySuffix (PutStr ":") (PutStr label) <$$--> body
- type (<++>) l r = PrettyInfix PrettyEmpty l r
- type (<+>) l r = PrettyInfix PrettySpace l r
- type (<||>) l r = PrettyAlternative l r
- type (<$$>) l r = PrettyInfix PrettyNewline l r
- type (<$$-->) l r = PrettyInfix PrettyNewline l (PrettyIndent 2 r)
- type PrettyParens doc = PrettySurrounded (PutStr "(") (PutStr ")") doc
- type PrettySurrounded open close doc = (open <++> doc) <++> close
- type PrettyWide docs = PrettyMany PrettySpace docs
- type PrettyHigh docs = PrettyMany PrettyNewline docs
- type PrettyManyIn sep docs = PrettySurrounded sep sep (PrettyMany sep docs)
- type family PrettyMany (sep :: PrettyType) (docs :: [PrettyType]) :: PrettyType where ...
- type family PrettyOften (n :: Nat) (doc :: PrettyType) :: PrettyType where ...
- data PrettyType where
- PrettyEmpty :: PrettyType
- PrettySpace :: PrettyType
- PrettyNewline :: PrettyType
- PrettySymbol :: PrettyPadded -> PrettyPrecision -> Symbol -> PrettyType
- PrettyNat :: PrettyPadded -> PrettyPrecision -> PrettyNatFormat -> Nat -> PrettyType
- PrettyPrefix :: PrettyType -> PrettyType -> PrettyType
- PrettyInfix :: PrettyType -> PrettyType -> PrettyType -> PrettyType
- PrettySuffix :: PrettyType -> PrettyType -> PrettyType
- PrettyIndent :: Nat -> PrettyType -> PrettyType
- PrettyAlternative :: PrettyType -> PrettyType -> PrettyType
- data PrettyPadded where
- data PrettyPrecision where
- data PrettyNatFormat
- class PrettyTypeShow p where
- type PTM a = RWS Indentation String PTRenderState a
- writeIndented :: String -> PTM ()
- type Indentation = Int
- data PTRenderState
- class PrintfArgModifier a where
Pretty Printing Types
Arguments
| :: forall (t :: k). PrettyTypeShow (ToPretty t) | |
| => proxy t | A proxy to the type to print. A |
| -> String |
Pretty print either types of kind PrettyType or any other type with a
ToPretty instance.
type family ToPretty (a :: k) :: PrettyType Source #
Create a PrettyType from a type.
This is a type-level equivalent of the Show class.
Write an instance of this for converting your type (preferrable of your
kind also) to a promoted PrettyType.
Instances
| type ToPretty PrettyType t Source # | |
Pretty Printing
Pretty Printing Strings (Symbol)
type PutStr str = PrettySymbol PrettyUnpadded PrettyPrecise str Source #
A PrettyType for a string.
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.
Pretty Printing Numbers (Nat)
type PutNat x = PrettyNat PrettyUnpadded PrettyPrecise PrettyDec x Source #
A PrettyType for a number.
type PutNatW width x = PrettyNat (PrettyPadded width) PrettyPrecise PrettyDec x Source #
A PrettyType for a number with a width.
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,
>>>showPretty (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,
>>>showPretty (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,
>>>showPretty (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,
>>>showPretty (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,
>>>showPretty (Proxy :: Proxy (PutBits64 5))"00000000000000000000000000000000000000000000000000000000000000000000101"
Composing Pretty Printers
type (<:>) label body = PrettySuffix (PutStr ":") (PutStr label) <+> body infixl 5 Source #
A label followed by a colon and space : followed by another element.
>>>showPretty (Proxy :: Proxy ("foo" <:> PutStr "bar"))@ foo: bar @
type (<:$$>) label body = PrettySuffix (PutStr ":") (PutStr label) <$$> body infixl 5 Source #
Like <:> but begin the body on a new line.
>>>showPretty (Proxy :: Proxy (PutStr "foo" <:$$> PutStr "bar"))@ foo: bar @
type (<:$$-->) label body = PrettySuffix (PutStr ":") (PutStr label) <$$--> body infixl 3 Source #
Like '<:$$__>' but indent the body with two spaces.
>>>showPretty (Proxy :: Proxy (PutStr "foo" <:$$--> PutStr "bar"))@ foo: bar @
type (<++>) l r = PrettyInfix PrettyEmpty l r infixl 6 Source #
Concatenate two PrettyType.
type (<+>) l r = PrettyInfix PrettySpace l r infixl 5 Source #
Concatenate two PrettyType using a PrettySpace.
type (<||>) l r = PrettyAlternative l r infixl 5 Source #
Choose the first non-empty from two PrettyTypes.
type (<$$>) l r = PrettyInfix PrettyNewline l r infixl 4 Source #
Concatenate two PrettyType using a PrettyNewline.
type (<$$-->) l r = PrettyInfix PrettyNewline l (PrettyIndent 2 r) infixl 3 Source #
Concatenate two PrettyType using a PrettyNewline and indent the second.
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
Pretty Printing Lists
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.:
>>>showPretty (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 |
Basic Building Blocks
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.
Constructors
| PrettyEmpty :: PrettyType | |
| PrettySpace :: PrettyType | |
| PrettyNewline :: PrettyType | Begin a newline. Always use this otherwise indentation will not work! |
| PrettySymbol :: PrettyPadded -> PrettyPrecision -> Symbol -> PrettyType | |
| PrettyNat :: PrettyPadded -> PrettyPrecision -> PrettyNatFormat -> Nat -> PrettyType | |
| PrettyPrefix :: PrettyType -> PrettyType -> PrettyType | Prefix the second with the first argument, but only if it (the second) has content. |
| PrettyInfix :: PrettyType -> PrettyType -> PrettyType -> PrettyType | Combine the last to arguments with the first in between them, but only if both have content. |
| PrettySuffix :: PrettyType -> PrettyType -> PrettyType | Add a the first argument as suffix to the second argument, but only if the second has content. |
| PrettyIndent :: Nat -> PrettyType -> PrettyType | Indentation. Prefix any line using the given number of |
| PrettyAlternative :: PrettyType -> PrettyType -> PrettyType | Alternative rendering, if the first document ist empty the second will be rendered. |
Instances
| type ToPretty PrettyType t Source # | |
data PrettyPadded where Source #
Padding for PrettyTypes PrettySymbol and PrettyNat.
Constructors
| PrettyUnpadded :: PrettyPadded | No minimum or fixed width |
| PrettyPadded :: Nat -> PrettyPadded | Pad a |
Instances
| PrintfArgModifier PrettyPadded PrettyUnpadded Source # | Translation of |
| KnownNat p => PrintfArgModifier PrettyPadded (PrettyPadded p) Source # | Translation of |
data PrettyPrecision where Source #
The precision for PrettySymbol and PrettyNat.
Constructors
| PrettyPrecise :: PrettyPrecision | No minimum precision. |
| PrettyPrecision :: Nat -> PrettyPrecision | Precision, for |
Instances
| PrintfArgModifier PrettyPrecision PrettyPrecise Source # | Translation of |
| KnownNat p => PrintfArgModifier PrettyPrecision (PrettyPrecision p) Source # | Translation of |
data PrettyNatFormat Source #
PrettyNat formatting options.
Constructors
| PrettyHex | Hexa decimal rendering:
|
| PrettyHexU | Hexa decimal rendering (upper case):
|
| PrettyDec | Decimal rendering:
|
| PrettyBit | Binary rendering:
|
Instances
| PrintfArgModifier PrettyNatFormat PrettyHex Source # | |
| PrintfArgModifier PrettyNatFormat PrettyHexU Source # | Translation of |
| PrintfArgModifier PrettyNatFormat PrettyDec Source # | |
| PrintfArgModifier PrettyNatFormat PrettyBit Source # | |
Pretty Rendering
class PrettyTypeShow p where Source #
An internal type class for rendering the types of kind PrettyType.
Minimal complete definition
Methods
ptShow :: proxy p -> PTM () Source #
Given any proxy to a promoted constructor of PrettyType, generate a
String.
ptHasContent :: proxy p -> PTM Bool Source #
Instances
type PTM a = RWS Indentation String PTRenderState a Source #
writeIndented :: String -> PTM () Source #
Internal; write a possibly indented string, and update the PTRenderState accordingly.
data PTRenderState Source #
Constructors
| AtBeginningOfLine | |
| AlreadyIndented |
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
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 # | |
| PrintfArgModifier PrettyNatFormat PrettyHexU Source # | Translation of |
| PrintfArgModifier PrettyNatFormat PrettyDec Source # | |
| PrintfArgModifier PrettyNatFormat PrettyBit Source # | |
| PrintfArgModifier PrettyPrecision PrettyPrecise Source # | Translation of |
| PrintfArgModifier PrettyPadded PrettyUnpadded Source # | Translation of |
| KnownNat p => PrintfArgModifier PrettyPrecision (PrettyPrecision p) Source # | Translation of |
| KnownNat p => PrintfArgModifier PrettyPadded (PrettyPadded p) Source # | Translation of |