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


___
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 nadine.and.he...@pobox.comwrote:

 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


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



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


[Haskell-cafe] Re: generics question 2

2006-04-04 Thread Frederik Eaton
Hi Ralf,

Thanks. I'm sorry, now I think that wasn't the source of my problem. 
What I want to do is specialise not to a specific type like Bool but
to the class of all pairs (a,b). But this causes the compiler to
complain, even for simpler examples:

cast True :: (Typeable a, Typeable b) = Maybe (a,b)

interactive:1:0:
Ambiguous type variable `a' in the constraints:
  `Typeable a' arising from instantiating a type signature at 
interactive:1:0-51
  `Show a' arising from use of `print' at Top level
Probable fix: add a type signature that fixes these type variable(s)

interactive:1:0:
Ambiguous type variable `b' in the constraints:
  `Typeable b' arising from instantiating a type signature at 
interactive:1:0-51
  `Show b' arising from use of `print' at Top level
Probable fix: add a type signature that fixes these type variable(s)

Is there a way to solve this, or do I have to avoid polymorphism? I
can use 'toConstr' to find out dynamically if a particular type is a
pair, and then use unsafeCoerce, but I hear that unsafeCoerce is
unsafe.

Frederik

On Mon, Apr 03, 2006 at 05:41:55PM -0700, Ralf Lammel wrote:
  Hi Ralf,
  
  I'm looking for a function like extT but with more general type:
  
  (t a - s a) - (t b - s b) - (t a - s a)
  
  Is there such a thing in the generics library?
 
 Hi Frederik,
 
 Not sure how you are exactly going to use such an operation ...
 But here is its implementation anyhow.
 Thanks for the riddle.
 
 Ralf
 
 import Data.Generics
 
 -- Frederik's weird ext operation :-)
 ext' :: (Data (t a), Data (s a), Data (t b), Data (s b))
  = (t a - s a) - (t b - s b) - (t a - s a)
 ext' f g ta = case cast g of
Just g' - g' ta
Nothing - f ta
 
 -- A generic default
 f (Just x) = [x]
 f Nothing  = []
 
 -- A type-specific case
 g (Just True)  = [True]
 g (Just False) = []
 g Nothing  = []
 
 -- A composition using our new type-extension operator
 test :: Data a = Maybe a - [a]
 test = ext' f g
 
 -- Let's see whether it works ...
 main = do 
   print $ test (Just (1::Int))
   print $ test (Just False)
 
 

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


[Haskell-cafe] RE: generics question 2

2006-04-04 Thread Ralf Lammel
Hi Frederik,

[resending; as it bounced because of size.]
That’s a tricky one.
Let’s first recall that this one is still fine:

*Main :t cast True :: (Typeable a, Typeable b) = Maybe (a,b)
cast True :: (Typeable a, Typeable b) = Maybe (a,b) :: (Typeable b,
 Typeable a) =
    Maybe (a, b)

The type error for your attempt was caused by the attempt to print this 
polymorphic maybe.
The overloading resolution for the show instance cannot possibly deal with this 
polymorphism.
More generally, any dependent SYB functionality or class-based code would run 
into this problem.

However, the above polymorphic cast, as such does not work as you would expect.
Here is a clear example:

sigh = maybe 0 (\(a,b) - gsize a + gsize b) (cast True)

The component types of this product are *ambiguous*.
Cast is monomorphic. No way to use it for polymorphic problems.
So we need polymorphic type extension, here: dataCast2 provided by the Data 
class.

So here is how it works with polymorphic type extension.
See below and check out the 2nd paper for some deeper discussion.
Or if you find this all too complicated, use class-based SYB style (3rd SYB 
paper).
Thanks for keeping me off the street. ☺

Regards,
Ralf

import Data.Generics

--
-- A weird gsize function
--

g :: Data a = a - Int

g = gsize `extQ` (\(x::Int) - x) `ext2Q` f

 where

  f :: (Data a, Data b) = (a,b) - Int

  f (a,b) = g a + g b + 1

--
-- | Flexible type extension
-- Should be in Data.Generics.Aliases
--

ext2 :: (Data a, Typeable2 t)
 = c a
 - (forall a b. (Data a, Data b) = c (t a b))
 - c a

ext2 def ext = maybe def id (dataCast2 ext)


--
-- | Type extension of transformations for unary type constructors
-- Should be in Data.Generics.Aliases
--

ext2T :: (Data d, Typeable2 t)
  = (forall d. Data d = d - d)
  - (forall d d'. (Data d, Data d') = t d d' - t d d')
  - d - d

ext2T def ext = unT ((T def) `ext2` (T ext))


--
-- | Type extension of queries for type constructors
-- Should be in Data.Generics.Aliases
--

ext2Q :: (Data d, Typeable2 t)
  = (d - q)
  - (forall d d'. (Data d, Data d') = t d d' - q)
  - d - q

ext2Q def ext = unQ ((Q def) `ext2` (Q ext))


--
-- | The type constructor for transformations
-- Not exported from Data.Generics.Aliases
--

newtype T x = T { unT :: x - x }


--
-- | The type constructor for queries
-- Not exported from Data.Generics.Aliases
--

newtype Q q x = Q { unQ :: x - q }


--
-- Time to test
--

data Foo = Foo1 Int | Foo2 (Int,Int) deriving (Typeable, Data, Show)

main = do 
  print $ gmapQ g (Foo1 88)
  print $ gmapQ g (Foo2 (21,20))

 -Original Message-
 From: Frederik Eaton [mailto:[EMAIL PROTECTED]

 What I want to do is specialise not to a specific type like Bool but
 to the class of all pairs (a,b). But this causes the compiler to
 complain, even for simpler examples:
 
 cast True :: (Typeable a, Typeable b) = Maybe (a,b)
 
 interactive:1:0:
 Ambiguous type variable `a' in the constraints:
   `Typeable a' arising from instantiating a type signature at
 interactive:1:0-51
   `Show a' arising from use of `print' at Top level
 Probable fix: add a type signature that fixes these type variable(s)
 
 interactive:1:0:
 Ambiguous type variable `b' in the constraints:
   `Typeable b' arising from instantiating a type signature at
 interactive:1:0-51
   `Show b' arising from use of `print' at Top level
 Probable fix: add a type signature that fixes these type variable(s)
 
 Is there a way to solve this, or do I have to avoid polymorphism? I
 can use 'toConstr' to find out dynamically if a particular type is a
 pair, and then use unsafeCoerce, but I hear that unsafeCoerce is
 unsafe.

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


[Haskell-cafe] RE: generics question 2

2006-04-03 Thread Ralf Lammel
 Hi Ralf,
 
 I'm looking for a function like extT but with more general type:
 
 (t a - s a) - (t b - s b) - (t a - s a)
 
 Is there such a thing in the generics library?

Hi Frederik,

Not sure how you are exactly going to use such an operation ...
But here is its implementation anyhow.
Thanks for the riddle.

Ralf

import Data.Generics

-- Frederik's weird ext operation :-)
ext' :: (Data (t a), Data (s a), Data (t b), Data (s b))
 = (t a - s a) - (t b - s b) - (t a - s a)
ext' f g ta = case cast g of
   Just g' - g' ta
   Nothing - f ta

-- A generic default
f (Just x) = [x]
f Nothing  = []

-- A type-specific case
g (Just True)  = [True]
g (Just False) = []
g Nothing  = []

-- A composition using our new type-extension operator
test :: Data a = Maybe a - [a]
test = ext' f g

-- Let's see whether it works ...
main = do 
  print $ test (Just (1::Int))
  print $ test (Just False)


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