GenericPretty: A generic, derivable, haskell pretty printer.

[ bsd3, generics, library, pretty-printer, text ] [ Propose Tags ]

GenericPretty is a haskell library that provides support for automatic derivation of pretty printing functions on user defined data types. The Pretty library http://www.haskell.org/ghc/docs/7.0.4/html/libraries/ghc-7.0.4/Pretty.html is used underneath, the work is done over Pretty.Doc types.

The output provided by the library functions is identical to that of Prelude.show, except it has extra whitespace.

This requires the use of the new GHC.Generics features: http://www.haskell.org/haskellwiki/Generics. These seem to be present in the GHC HEAD development snapshots >= 7.1.20110601.

The Generics used are based on those described in the paper "A Generic Deriving Mechanism for Haskell" : http://dreixel.net/research/pdf/gdmh.pdf . The changes from the original paper on the ghc implementation are described here: http://www.haskell.org/haskellwiki/Generics#Changes_from_the_paper.

For more info and examples of usage please see the README file included in the package and the API at http://haggismcmutton.github.com/GenericPretty/


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0, 0.1.1, 0.1.2, 0.1.3, 1.0.0, 1.0.1, 1.1.0, 1.1.1, 1.1.2, 1.1.3, 1.1.4, 1.1.5, 1.1.6, 1.1.7, 1.1.8, 1.1.9, 1.2.0, 1.2.1, 1.2.2
Dependencies base (>=3 && <5), ghc (>=7.1.20110601), ghc-prim [details]
License BSD-3-Clause
Author Razvan Ranca
Maintainer ranca.razvan@gmail.com
Category Text, Generics, Pretty Printer
Home page https://github.com/HaggisMcMutton/GenericPretty
Source repo head: git clone git@github.com:HaggisMcMutton/GenericPretty.git
Uploaded by RazvanRanca at 2011-08-10T03:42:38Z
Distributions LTSHaskell:1.2.2, NixOS:1.2.2, Stackage:1.2.2
Reverse Dependencies 18 direct, 14 indirect [details]
Downloads 20745 total (63 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for GenericPretty-1.0.0

[back to package description]
GenericPretty. A Generic, Derivable, Haskell Pretty Printer
===============================================================================

GenericPretty is a haskell library that provides support for automatic
derivation of pretty printing functions on user defined data types.

The Pretty library [1] is used underneath, the work is done over "Doc" types.

The output provided by the library functions is identical to that of 
Prelude.show, except it has extra whitespace.
	
This library requires the use of the new GHC.Generics features [2]
As of 9.08.2011, these aren't present in the stable GHC releases, but 
seem to be present in the GHC HEAD development snapshots >= 7.1.20110601.

The Generics used are based on those described in the paper 
"A Generic Deriving Mechanism for Haskell" [3].
There are however several changes between the mechanism described in the
paper and the one implemented in GHC [4].

I find examples are the best aid in understanding. So, here is a  
haskell source file, called 'SimpleTest.hs'
----------------------------------------------------
{-# LANGUAGE DeriveGeneric #-}

import Text.PrettyPrint.GenericPretty

data Tree a = Leaf a | Node (Tree a) (Tree a) deriving (Generic)

instance (Out a) => Out (Tree a) where
	docPrec = genOut

tree1 :: Tree Int
tree1 = Node (Node (Leaf 333333) (Leaf (-555555)))(Node (Node(Node(Leaf 888888) 
		(Leaf 57575757))(Leaf (-14141414)))(Leaf 7777777))
			
main = pp tree1
------------------------------------------------
The flag DeriveGeneric must be given to GHC. This can be done as above, 
in a 'LANGUAGE' pragma, or manually by compiling with 'ghc -XDeriveGeneric'.

As can be seen, to use the library one must simply import it, derive 'Generic' 
on the custom data type, and write an instance of 'Out' using 'genOut'.

Then one can use the pretty printing functions, such as 'pp' and 'pretty'.

Compiling and running the file is simple and gives the following result.
-----------------------------
$ ghc SimpleTest.hs
$ SimpleTest

Node (Node (Leaf 333333) (Leaf (-555555)))
     (Node (Node (Node (Leaf 888888) (Leaf 57575757)) (Leaf (-14141414)))
           (Leaf 7777777))
---------------------------
If we replaced the main function with 'main = ppLen 30 tree1', 
the result would instead be:

Node (Node (Leaf 333333)
           (Leaf (-555555)))
     (Node (Node (Node (Leaf 888888)
                       (Leaf 57575757))
                 (Leaf (-14141414)))
           (Leaf 7777777))
		   
In this case the output tries to remain under 30 characters/line, if possible, 
while always maintaining correct indentation.

Customizing the pretty printed results is also straightforward, as in the
following example called 'CustomTest.hs'
----------------------------
{-# LANGUAGE DeriveGeneric #-}

import Text.PrettyPrint.GenericPretty
import Pretty

data Tree a = Leaf a | Node (Tree a) (Tree a) deriving (Generic)

instance (Out a) => Out (Tree a) where
  docPrec n (Leaf a) =  parens $ text "customLeaf" <+> docPrec n a
  docPrec n (Node a b) = parens $ text "customNode" $$ nest 1 (docPrec n a) 
                                                    $$ nest 1 (docPrec n b)

tree1 :: Tree Int
tree1 = Node (Node (Leaf 333333) (Leaf (-555555)))(Node (Node(Node(Leaf 888888) 
		(Leaf 57575757))(Leaf (-14141414)))(Leaf 7777777))
			
main = pp tree1
------------------------------
Here we import the library 'Pretty' and use it directly to define docPrec.
By running the above we get a tree with a minimum of indentation:

(customNode
  (customNode
    (customLeaf 333333)
    (customLeaf -555555))
  (customNode
    (customNode
      (customNode
        (customLeaf 888888)
        (customLeaf 57575757))
      (customLeaf -14141414))
    (customLeaf 7777777)))

-----------------------------------
The above 'Tree' examples can be found in 'TestSuite/SimpleTest.hs' 
and 'TestSuite/CustomTest.hs'. More involved examples integrated 
with QuickCheck can be found in 'TestSuite/Tests.hs'.

Further information can be found in the API at 
http://haggismcmutton.github.com/GenericPretty/ and in the source code itself.
===============================================================================

Please send any questions/suggestions to:
Razvan Ranca <ranca.razvan@gmail.com>

===============================================================================

[1] http://www.haskell.org/ghc/docs/7.0.4/html/libraries/ghc-7.0.4/Pretty.html
[2] http://www.haskell.org/haskellwiki/Generics
[3] http://dreixel.net/research/pdf/gdmh.pdf
[4] http://www.haskell.org/haskellwiki/Generics#Changes_from_the_paper