Hi Max,<br> <br><div class="gmail_quote"><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">EMGM&#39;s<br>
map demands traversion function to be non-polymorphic, i.e. type-checker<br>
fails with the message, complaining it cannot match `E a` against<br>
`E Name`, against `E Salary` etc.</blockquote><div><br>I&#39;m wondering if you tried everywhere&#39; (or everywhere) [1]. Here&#39;s one solution, but I&#39;m not sure if it does what you what it to.<br><br>--<br><br>{-# LANGUAGE MultiParamTypeClasses #-}<br>

{-# LANGUAGE FlexibleContexts #-}<br>{-# LANGUAGE FlexibleInstances #-}<br>{-# LANGUAGE UndecidableInstances #-}<br>{-# LANGUAGE TemplateHaskell #-}<br><br>module Rows where<br><br>import qualified Generics.EMGM as G<br>
import Generics.EMGM.Derive<br>
<br>data Row = Row (Either (Maybe Int) (Maybe String)) (Either (Maybe Int) (Maybe Float)) (Either (Maybe Int) (Maybe Integer))<br>  deriving Show<br><br>$(derive &#39;&#39;Row)<br><br>gmap :: (Rep (Everywhere&#39; (Either (Maybe Int) (Maybe a))) Row) =&gt; (Either (Maybe Int) (Maybe a) -&gt; Either (Maybe Int) (Maybe a)) -&gt; Row -&gt; Row<br>

gmap = G.everywhere&#39; -- top-down<br><br>readRow :: [String] -&gt; Row -&gt; Row<br>readRow l = gmap app<br>  where<br>    app :: Either (Maybe Int) (Maybe String) -&gt; Either (Maybe Int) (Maybe String)<br>    app (Left (Just ri)) = Right (l `atMay` ri &gt;&gt;= G.read)<br>

    app x = x<br><br>atMay :: [a] -&gt; Int -&gt; Maybe a<br>atMay = undefined<br><br>--<br><br>This appears to implement your desired functionality. Here are some points to note about what I did to get it working:<br><br>

* EMGM has problems resolving type synonyms, so I expanded your E here.<br>* I just defined gmap to show what the type signature would be here. You could get rid of gmap and just use everywhere&#39;.<br>* I used everywhere&#39; instead of everywhere, because you appear to want a top-down traversal. Depending on your types, it may not matter.<br>

* I gave app a concrete type signature, because as you noted, EMGM needs to be non-polymorphic here.<br>* I also gave app a fallback case, so you don&#39;t get any unexpected surprises at runtime.<br>* I used EMGM&#39;s read function [2] which seemed to be what you wanted for readMay. You could still use readMay here, of course.<br>

<br>[1] <a href="http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMGM-Functions-Everywhere.html">http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMGM-Functions-Everywhere.html</a><br>

[2] <a href="http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMGM-Functions-Read.html">http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/Generics-EMGM-Functions-Read.html</a><br><br>

Regards,<br>Sean<br></div></div>