PPrinter-0.0.2: A generic derivable Haskell pretty printer

Copyright(c) The University of Edinburgh 2016
LicenseBSD-style (see the file LICENSE)
MaintainerYi Zhen <s1563190@sms.ed.ac.uk>
StabilityUnknown
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Text.PPrinter

Description

Provides a collection of pretty printer combinators, a set of API's that provides a way to easily print out text in a consistent format.

Originally designed by Philip Wadler's.

For more information you can refer to the original paper that serves as the basis for this libraries design: A prettier printer, by Philip Wadler, 2003.

Synopsis

Documentation

class Pretty a where Source

Conversion of values to pretty printable Strings

Derived instances of Pretty have the following properties

  • The result of ppPrec is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined to be an infix operator, then ppPrec will produce infix applications of the constructor.
  • If the constructor is defined using record syntax, then ppPrec will produce the record-syntax form, with the fields given in the same order as the original declaration.

Minimal complete definition

ppPrec | pp

Methods

ppPrec Source

Arguments

:: Int

the operator precedence of the enclosing context

-> a

the value to be converted to a String

-> DOC

the result

ppPrec converts a value to a pretty printable DOC.

pp :: a -> DOC Source

pp is the equivalent of show

genList :: [a] -> DOC Source

ppList :: [a] -> DOC Source

ppList is the equivalent of showList

Instances

Pretty Bool Source 
Pretty Char Source 
Pretty Double Source 
Pretty Float Source 
Pretty Int Source 
Pretty Integer Source 
Pretty Ordering Source 
Pretty () Source 
Pretty a => Pretty [a] Source 
Pretty a => Pretty (Maybe a) Source 
(Pretty a, Pretty b) => Pretty (Either a b) Source 
(Pretty a, Pretty b) => Pretty (a, b) Source 
(Pretty a, Pretty b) => Pretty (Map a b) Source 
(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) Source 
(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) Source 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) Source 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) Source 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) Source 
(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) Source 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i) => Pretty (a, b, c, d, e, f, g, h, i) Source 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j) => Pretty (a, b, c, d, e, f, g, h, i, j) Source 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k) => Pretty (a, b, c, d, e, f, g, h, i, j, k) Source 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l) Source 

printer :: Show a => Pretty a => a -> IO () Source

printLen :: Show a => Pretty a => Int -> a -> IO () Source

fullPrinter :: Show a => Pretty a => Style -> a -> IO () Source

The default Pretty Printer

pprint :: Pretty a => Int -> a -> IO () Source

pshow :: Pretty a => (Doc -> [Char]) -> Int -> a -> String Source

pretty :: (Doc -> [Char]) -> Int -> DOC -> String Source

(<>) :: DOC -> DOC -> DOC infixr 6 Source

nil :: DOC Source

nest :: Int -> DOC -> DOC Source

text :: String -> DOC Source

line :: DOC Source

group :: DOC -> DOC Source

parens :: DOC -> DOC Source

layout :: Doc -> [Char] Source

char :: Char -> DOC Source

rep :: [DOC] -> DOC Source

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (Maybe a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Proxy * t) 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (M1 i c f p) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g)