[Haskell-cafe] A generics question

Jason Dagit dagit at codersbase.com
Mon Jun 8 20:20:45 EDT 2009


On Mon, Jun 8, 2009 at 4:10 PM, Henry Laxen <nadine.and.henry at pobox.com>wrote:

> 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)


What about making both of these instances of Enum instead of using Data and
Typeable?

You'd get fromEnum and toEnum.  Which I think, would give you the int
mapping that you are after.

fromEnum :: Enum a => a -> Int
toEnum :: Enum a => Int -> a

Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090608/50574287/attachment.html


More information about the Haskell-Cafe mailing list