
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