[Haskell-cafe] ANNOUNCE: Extensible and Modular Generics for the Masses: emgm-0.2

Sean Leather leather at cs.uu.nl
Fri Jan 30 09:28:53 EST 2009


==============================================
Extensible and Modular Generics for the Masses
==============================================

Extensible and Modular Generics for the Masses (EMGM) is a library for
generic programming in Haskell using type classes and a sum-of-products
view.

------------
Introduction
------------

emgm-0.2 is the second major release of the EMGM library.

A lot of work has been done since the initial release to build a solid set
of functions that will allow you to derive the necessary declarations for
using EMGM with your datatype. Thus, you don't have to write much code to
get started.

A great deal of documentation has also been added. There's a comprehensive
new entry page for Generics.EMGM that should help one figure out what to do
with this library. We plan to publish articles providing more examples as
well.

With these two improvements, you have no more excuses for not trying it out.
Download EMGM and see what you can do, generically!

------------
New Features
------------

Improvements over emgm-0.1 include:

*  Derive type representation using Template Haskell [1]
*  Major improvement in documentation with Haddock
*  bimap function [2]


[1] Here is a snippet from the documentation that shows what you save when
using TH over manual implementation.

> {-# LANGUAGE TemplateHaskell #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE OverlappingInstances #-}
> {-# LANGUAGE UndecidableInstances #-}

> module Example where
> import Generics.EMGM
> data T a = C a Int

> $(derive ''T)

The $(derive ''T) declaration in the above example generates the following
code:

1. Constructor description declarations (1 per constructor)

> conC :: ConDescr
> conC = ConDescr "C" 2 [] Nonfix

2. Embedding-projection pair declarations (1 per type)

> epT :: EP (T a) (a :*: Int)
> epT = EP fromT toT
>   where fromT (C v1 v2) = v1 :*: v2
>         toT (v1 :*: v2) = C v1 v2

3. Rep instance (1 per type)

> instance (Generic g, Rep g a, Rep g Int) => Rep g (T a) where
>   rep = rtype epT (rcon conC (rprod rep rep))

4. Higher arity instances if applicable (either FRep, FRep2, and FRep3
together, or BiFRep2)

> instance (Generic g) => FRep g T where
>   frep ra = rtype epT (rcon conC (rprod ra rint))

In this case, similar instances would be generated for FRep2 and FRep3.

5. Function-specific instances (1 per type)

> instance Rep (Collect Char) Char where
>   rep = Collect (:[])


[2] EMGM has a new function bimap and its related representation type class
BiFRep2:

> bimap :: (BiFRep2 Map f) => (a -> c) -> (b -> d) -> f a b -> f c d

With bimap, you can do the following in GHCi:

*Generics.EMGM Data.Char Prelude> bimap ord chr ('a',65)
(97,'A')
*Generics.EMGM Data.Char Prelude> bimap (++" So Long!") (const 42) (Right
"Earth")
Right 42

-------------------
General Information
-------------------

Visit the home page:

 http://www.cs.uu.nl/wiki/GenericProgramming/EMGM

----------------
General Features
----------------

The primary features of EMGM include:

*  Datatype-generic programming using sum-of-product views
*  Large collection of ready-to-use generic functions
*  Included support for standard datatypes: lists, Maybe, tuples
*  Easy to add support for new datatypes
*  Type classes make writing new functions straightforward in a structurally
inductive style
*  Generic functions are extensible with ad-hoc cases for arbitrary
datatypes
*  Good performance of generic functions

The features of this distribution include:

*  The API is thoroughly documented with Haddock
*  Fully tested with QuickCheck and HUnit
*  Program coverage ensures that all useful code has been touched by tests
*  Tested on both Mac and Windows systems

------------
Requirements
------------

EMGM has the following requirements:

*  GHC 6.8.1 - It has been tested with versions 6.8.3 and 6.10.1
*  Cabal library 1.2.1 - It has been tested with versions 1.2.4.0 and
1.6.0.1.

-----------------
Download & Source
-----------------

Use caball-install:

 cabal install emgm

Get the package:

 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/emgm

Check out the current source with Subversion:

 svn checkout https://svn.cs.uu.nl:12443/repos/dgp-haskell/EMGM/trunk

Or view it online:

  https://svn.cs.uu.nl:12443/viewvc/dgp-haskell/EMGM/trunk/

--------
Examples
--------

Check out the examples:

 https://svn.cs.uu.nl:12443/viewvc/dgp-haskell/EMGM/trunk/examples/

--------------
Bugs & Support
--------------

Report issues or request features:

  http://code.google.com/p/emgm/issues/list

Discuss EMGM with the authors, maintainers, and other interested persons:

 http://www.haskell.org/mailman/listinfo/generics

-------
Credits
-------

The research for EMGM originated with Ralf Hinze. It was extended with work
by Bruno Oliveira and Andres Löh. More details of the library functionality
were explored by Alexey Rodriguez. We are very grateful to all of these
people for the foundation on which this library was built.

The current authors and maintainers of EMGM are:

*  Sean Leather
*  José Pedro Magalhães
*  Alexey Rodriguez
*  Andres Löh
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090130/430e6526/attachment.htm


More information about the Haskell-Cafe mailing list