[Haskell-cafe] A generics question

Henry Laxen nadine.and.henry at pobox.com
Mon Jun 8 19:10:18 EDT 2009


Lets suppose I have a file that has encoded things of different
types as integers, and now I would like to convert them back
into specific instances of a data type.  For example, I have a
file that contains 1,1,2,3 and I would like the output to be
[Red, Red, Green, Blue]. I also would like to do this
generically, so that if I wanted to convert the same list of
integers into say Sizes, I would get [Small, Small, Medium,
Large]  Now please have a look at the following code:

{-# LANGUAGE DeriveDataTypeable #-}
import Data.Generics
data Color = Red | Green | Blue deriving (Eq,Ord,Read,Show,Typeable,Data)
data Size  = Small | Mediaum | Large deriving (Eq,Ord,Read,Show,Typeable,Data)
g = Green

c = undefined :: Color
s = undefined :: Size

t = do
  print $   toConstr g  -- Green
  print $ dataTypeOf c  -- DataType {tycon = "Main.Color", datarep = AlgRep
[Red,Green,Blue]}

convert :: (Data a, Data b) =Int -a -b
convert i x =
  let c = dataTypeConstrs (dataTypeOf x) !! (i-1)
  in fromConstr c


I would like to be able to say: x = convert 1 c and have it
assign Red to x then I would like to say: y = convert 1 s and
have it assign Small to y, however, when I try that I get:

    Ambiguous type variable `b' in the constraint:
      `Data b' arising from a use of `convert' at <interactive>:1:8-18
    Probable fix: add a type signature that fixes these type variable(s)

Of course if I say x :: Color = convert 1 c, it works, but I
would like to avoid that if possible, as all of the information
is already contained in the parameter c.  Is there any way to do
this?  Thanks in advance for your wise counsel.

Best wishes,
Henry Laxen




More information about the Haskell-Cafe mailing list