
Hello, I was writing some Haskell when I stumbled on the following problem: With the following language extension...
{-# LANGUAGE RankNTypes #-}
... it's possible to define 'foo' and 'bar' like so:
foo :: (Num c, Num d) => (forall b. Num b => a -> b) -> a -> (c, d) foo f x = (f x, f x)
bar :: (Read c, Read d) => (forall b. Read b => a -> b) -> a -> (c, d) bar f x = (f x, f x)
Which allows us to write:
testFoo = foo fromInteger 1 :: (Int, Float) testBar = bar read "1" :: (Int, Float)
Now I would like to generalise 'foo' and 'bar' to 'bla' so that I can write: testBla1 = bla fromInteger 1 :: (Int, Float) testBla2 = bla read "1" :: (Int, Float) My question is how to define 'bla'. I can write:
bla :: (forall b. a -> b) -> a -> (c, d) bla f x = (f x, f x)
But then 'testBla1' gives the following expected error: Could not deduce (Num b) from the context () arising from a use of `fromInteger' Possible fix: add (Num b) to the context of the polymorphic type `forall b. a -> b' In the first argument of `bla', namely `fromInteger' In the expression: bla fromInteger 1 :: (Int, Float) In the definition of `testBla1': testBla1 = bla fromInteger 1 :: (Int, Float) And 'testBla2' gives a similar error complaining that it can't deduce (Read b) from the context. So, somehow I need to quantify over the type class. bla :: forall cls. (cls c, cls d) => (forall b. cls b => a -> b) -> a -> (c, d) But this isn't legal. Is there another way of defining 'bla'? Thanks, Bas
participants (1)
-
Bas van Dijk