Generics for constructing Rows

Hi, all. 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
readRow :: [String] -> Row -> Row readRow l = gmap (\(Left (Just ri)) -> Right $ l `atMay` c >>= readMay)
`atMay` and `readMay` are defined in module `Safe` from package `safe`
atMay :: [a] -> Int -> Maybe a readMay :: (Read a) => String -> Maybe a
Basically we have optional Row indices and try to read raw row (list of Strings) into the same Row type if index is present. At this moment I just have separate data type for row which has been read and just a list of row indices, but it is definitely flawed when I need to add fields to Row from time to time, as it is too easy to introduce bugs while positioning in list of row indices, not mentioning all those boilerplate code flowing around. I've tried to define gmap using libraries for generic programming but failed each time while type checking for different reasons. With `Data.Generics` and `gmapT` it fails because gmapT doesn't allow traversion function to have `Read a` constraint (Data and Typeable instances for Row and inner data types of course were derived). EMGM's map demands traversion function to be non-polymorphic, i.e. type-checker fails with the message, complaining it cannot match `E a` against `E Name`, against `E Salary` etc. For each of this I've spent smth about five hours just reading API docs, papers, and trying to beat type-checker. Maybe I'll look into Smash, RepLib and others, but I hope someone was also trying to define such gmap and succeeded. 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. Thanks in advance, Max.

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

Sean Leather
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.
That seems to be GP problem, as your solution doesn't scale well when I wan't to add/remove/change fields in the `Row` record. The perfect way as I see it, would be just editing `Row` data declaration, nothing else. Studying few papers about GP in Haskell, I reckon this could be represented as generic traversal, using my `Row` declaration with `Either`. I don't see really good way to write a generic producer from `[String]` to version of `Row` without `Either`. But SYB doesn't provide a way for passing type-class-parametric functions to gmapT, and SYB-with-class has large overhead of its usage. I don't have enough time to find out how this can be written in SYB-with-class, if it really can be written. The restriction of EMGM was described in my initial message.
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.
Many thanks for this code, I'll try to integrate it at this point. It seems to remove the burden of managing row indices list and implements some intended restrictions that will make my code less error prone, I hope. WBR, Max.

That seems to be GP problem, as your solution doesn't scale well when I wan't to add/remove/change fields in the `Row` record.
Ah yes, this is a good use case. I wasn't paying close enough attention before, and I didn't see an immediate implementation of your function at the time.
The perfect way as I see it, would be just editing `Row` data declaration, nothing else. Studying few papers about GP in Haskell, I reckon this could be represented as generic traversal, using my `Row` declaration with `Either`. I don't see really good way to write a generic producer from `[String]` to version of `Row` without `Either`. But SYB doesn't provide a way for passing type-class-parametric functions to gmapT, and SYB-with-class has large overhead of its usage. I don't have enough time to find out how this can be written in SYB-with-class, if it really can be written. The restriction of EMGM was described in my initial message.
I would suggest looking at Multirec. There's a draft of the paper to be published at ICFP, and the library is on Hackage. http://www.cs.uu.nl/wiki/GenericProgramming/Multirec http://hackage.haskell.org/package/multirec If you don't have anything generically useful by next week, I'll look at it again when I have more time. Regards, Sean

Hello,
On Thu, Aug 20, 2009 at 16:54, Max Desyatov
Sean Leather
writes: 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.
That seems to be GP problem, as your solution doesn't scale well when I wan't to add/remove/change fields in the `Row` record. The perfect way as I see it, would be just editing `Row` data declaration, nothing else. Studying few papers about GP in Haskell, I reckon this could be represented as generic traversal, using my `Row` declaration with `Either`. I don't see really good way to write a generic producer from `[String]` to version of `Row` without `Either`. But SYB doesn't provide a way for passing type-class-parametric functions to gmapT, and SYB-with-class has large overhead of its usage. I don't have enough time to find out how this can be written in SYB-with-class, if it really can be written. The restriction of EMGM was described in my initial message.
Indeed SYB doesn't work here because Typeable-based run-time type comparison only works for monomorphic types. Doing something like readRow l = gmapT (mkT (\(Left (Just ri) :: E Name) -> Right $ l `atMay` ri
= readMay))
would work, but this, of course, is not what you want. I'm guessing the polymorphic typeOf previously described by Oleg [1] could help here, were it integrated in SYB. I don't think syb-with-class will help you here, since it only adds modularity to the type-based function extension. I think you would still have to write a case for every field in the Row record. Multirec would possibly work, were it not for the fact that it doesn't support parametric datatypes yet... Cheers, Pedro [1] http://osdir.com/ml/haskell-cafe@haskell.org/2009-03/msg00212.html

Hi Max, EMGM's
map demands traversion function to be non-polymorphic, i.e. type-checker fails with the message, complaining it cannot match `E a` against `E Name`, against `E Salary` etc.
I'm wondering if you tried everywhere' (or everywhere) [1]. Here's one solution, but I'm not sure if it does what you what it to. -- {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE TemplateHaskell #-} module Rows where import qualified Generics.EMGM as G import Generics.EMGM.Derive data Row = Row (Either (Maybe Int) (Maybe String)) (Either (Maybe Int) (Maybe Float)) (Either (Maybe Int) (Maybe Integer)) deriving Show $(derive ''Row) gmap :: (Rep (Everywhere' (Either (Maybe Int) (Maybe a))) Row) => (Either (Maybe Int) (Maybe a) -> Either (Maybe Int) (Maybe a)) -> Row -> Row gmap = G.everywhere' -- top-down readRow :: [String] -> Row -> Row readRow l = gmap app where app :: Either (Maybe Int) (Maybe String) -> Either (Maybe Int) (Maybe String) app (Left (Just ri)) = Right (l `atMay` ri >>= G.read) app x = x atMay :: [a] -> Int -> Maybe a atMay = undefined -- This appears to implement your desired functionality. Here are some points to note about what I did to get it working: * EMGM has problems resolving type synonyms, so I expanded your E here. * I just defined gmap to show what the type signature would be here. You could get rid of gmap and just use everywhere'. * I used everywhere' instead of everywhere, because you appear to want a top-down traversal. Depending on your types, it may not matter. * I gave app a concrete type signature, because as you noted, EMGM needs to be non-polymorphic here. * I also gave app a fallback case, so you don't get any unexpected surprises at runtime. * I used EMGM's read function [2] which seemed to be what you wanted for readMay. You could still use readMay here, of course. [1] http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMG... [2] http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMG... Regards, Sean
participants (3)
-
José Pedro Magalhães
-
Max Desyatov
-
Sean Leather