[Haskell-cafe] RE: generics question 2

Ralf Lammel Ralf.Lammel at microsoft.com
Tue Apr 4 20:13:58 EDT 2006


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:frederik at a5.repetae.net]
>
> 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.



More information about the Haskell-Cafe mailing list