Re: [Haskell-cafe] A generics question

2009-06-08 Thread Stefan Holdermans

Henry,

Ah, pressed send way to early. Of course, the definition should change  
a little as well:


 convert :: Data a => Int -> a
 convert i = xwhere
 x = fromConstr ( dataTypeConstrs (dataTypeOf x) !! (i - 1) )

Cheers,

  Stefan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A generics question

2009-06-08 Thread Stefan Holdermans

Henry,

Jason pointed out:

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


To me, this would indeed seem the way to go for your particular example.

Moreover, as for generic producer functions in general, the pattern  
suggested by the Prelude would be to have


  c :: Color
  c = undefined

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

and then use it as in

  convert 1 `asTypeOf` c

You'll find out that in most cases the (pseudo) "type annotation"  
isn't really needed and the type of the value to produce can be  
determined automatically by the context.


Cheers,

  Stefan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A generics question

2009-06-08 Thread Sterling Clover

On Jun 8, 2009, at 7:10 PM, Henry Laxen wrote:


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



The type signature for 'convert' is throwing away the information you  
want.


Try it with the following type signature and it should work fine:

convert :: (Data a) => Int -> a -> a

Of course, as has been noted, SYB is a rather big sledgehammer for  
the insect in question.


Cheers,
S.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A generics question

2009-06-08 Thread Jason Dagit
On Mon, Jun 8, 2009 at 4:10 PM, Henry Laxen 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A generics question

2009-06-08 Thread Henry Laxen
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 :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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe