[Haskell-cafe] Design question

Sean Leather leather at cs.uu.nl
Wed Dec 16 12:13:02 EST 2009


Hi Lenny,


> i am not quite sure how to do this in the most elegant way:
>
> I have some data structures:
>
> data A = A Double
> data B = B Double
> data C = C Double
> ...
>
> and i want to allow only a subset in another data structure, so i did
> something like this:
>
>     data SubSet = SubSetA A | SubSetC C
>
> and use it in Foo:
>
>     data Foo = Foo [SubSet]
>
> No i want to perform a polymorphic operation on the contents of A,B,C, e.g.
>
> doSomething :: Foo -> [Double]
> doSomething (Foo s) = map doSomethingElse s
>

You can do things similar to this using one of the many generics libraries
for Haskell [1,2]. I'm not sure if this is exactly what you're after, but
here is a possibility using EMGM [3].

{-# LANGUAGE TemplateHaskell       #-}
> {-# LANGUAGE UndecidableInstances  #-}
> {-# OPTIONS -fglasgow-exts         #-}
>
> import Generics.EMGM
> import Generics.EMGM.Derive
>
> data A = A Double
> data B = B Double
> data C = C Double
>
> data Subset = SubsetA A | SubsetC C
>
> data Foo = Foo [Subset]
>
> $(deriveMany [''A,''B,''C,''Subset,''Foo])
>
> doSomething :: Foo -> [Double]
> doSomething = collect
>

In GHCi, I get the following:

*Main> doSomething (Foo [SubsetA (A 5.0),SubsetC (C 9.9)])
[5.0,9.9]

Other libraries to look at include SYB [4] and Uniplate [5].

Regards,
Sean

[1] http://hackage.haskell.org/packages/archive/pkg-list.html#cat:generics
[2] http://www.cs.uu.nl/research/techreps/UU-CS-2008-010.html
[3] http://www.cs.uu.nl/wiki/GenericProgramming/EMGM
[4] http://www.cs.uu.nl/wiki/GenericProgramming/SYB
[5] http://community.haskell.org/~ndm/uniplate/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091216/5f7d349e/attachment.html


More information about the Haskell-Cafe mailing list