[Haskell-cafe] Generics for constructing Rows
Sean Leather
leather at cs.uu.nl
Thu Aug 20 07:43:38 EDT 2009
Hi Max,
I've come into trouble defining function `gmap` which will work on these
> data types:
>
> > data Row = Row
> > (E Name)
> > (E Salary)
> > (E Department)
>
> > type E a = Either (Maybe RowIndex) (Maybe a)
>
> > type RowIndex = Int
>
> `RowIndex`, `Name`, `Salary`, `Department` have kind *
>
> pseudocode:
>
> > gmap :: (E a -> E a) -> Row -> Row
>
>
[...]
> So, generic programming folks, is it even possible to define such
> function? I don't really care about using GHC extensions, I don't care
> about code being portable, I just want to remove boilerplate and prevent
> introducing bugs.
>
I'm not sure the problem you're running into is strictly a generic
programming (GP) one. Typically, GP takes code that is often written and
generalizes it, so that it doesn't have to be written for multiple
datatypes.
For your problem, I think the first issue is figuring out how to write the
non-generic function. I don't know if this is exactly what you want, but you
can write a version of gmap using GADTs and rank-2 types. I've simplified
some types, but it should be easily transferable to your code. For example,
change the String, Float, etc. to your Salary, Department, whatever.
---
{-# LANGUAGE GADTs #-}
{-# LANGUAGE Rank2Types #-}
module Main where
data T a where
String :: T String
Float :: T Float
Integer :: T Integer
data Row = Row (Maybe String) (Maybe Float) (Maybe Integer)
deriving Show
f :: T a -> Maybe a -> Maybe a
f String (Just "a") = Just "z"
f _ x = x
gmap :: (forall a . T a -> Maybe a -> Maybe a) -> Row -> Row
gmap f (Row x y z) = Row (f String x) (f Float y) (f Integer z)
main = do
print $ gmap f $ Row Nothing (Just 5.4) (Just 3) -- ==> Row Nothing (Just
5.4) (Just 3)
print $ gmap f $ Row (Just "a") Nothing Nothing -- ==> Row (Just "z")
Nothing Nothing
---
If this is what you're looking for, then I think it might be possible to do
this more generally, though I haven't looked into it.
Regards,
Sean
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090820/dee8db10/attachment.html
More information about the Haskell-Cafe
mailing list