Actually none of these seem to work:

>{-# OPTIONS -fglasgow-exts #-}
>
>module Main where
>
>main :: IO ()
>main = putStrLn "OK"
>
>d :: (forall c . b c -> c) -> b (b a) -> a
>d f = f . f
>
>t0 = d id
>t1 = d head
>t2 = d fst

Load this into GHCI and you get:

Test.hs:11:7:
Couldn't match the rigid variable `c' against `b c'
`c' is bound by the polymorphic type `forall c. b c -> c' at Test.hs:11:5-8
Expected type: b c -> c
Inferred type: b c -> b c
In the first argument of `d', namely `id'
In the definition of `t0': t0 = d id


Test.hs:13:5:
   Inferred type is less polymorphic than expected
     Quantified type variable `c' escapes
     It is mentioned in the environment:
       t2 :: (c, (c, a)) -> a (bound at Test.hs:13:0)
   In the first argument of `d', namely `fst'
   In the definition of `t2': t2 = d fst
Failed, modules loaded: none.

Keean.


Jacques Carette wrote:

It is really too bad the 'middle' version does not work, ie

John Fairbarn's version



d1 :: (forall c . b c -> c) -> b (b a) -> a
d1 f = f . f



John Meacham's version (dual (?))



d2 :: (forall c . c -> b c) -> a -> b (b a)
d2 f = f . f



Or something in the middle



d3 :: forall e a b . (forall c . e c -> b c) -> (e a) -> (b a)
d3 f = f . f



but ghci -fglasgow-exts does not like it :-(

Jacques

_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell



_______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Reply via email to