Doaitse Swierstra wrote:
> Just to show what kind of problems we are currently facing. The
> following type checks in our EHC compiler and in Hugs, but not in the GHC:
> 
> module Test where
> 
> data T s = forall x. T (s -> (x -> s) -> (x, s, Int))

> 
> run :: (forall s . T s) -> Int
> run ts  = case ts of
>             T g -> let (x,_, b) =  g x id
>                    in b
> 
> 
> Doaitse Swierstra
> 


f :: Double -> (Char -> Double) -> (Char, Double, Int)
f double charToDouble = (undefined, double, 0)

t :: T Double
t = T f

-- And what will happen here:
run t = ...

The "id" in "T g = g _ id" tries to require that
f :: Double -> (Double -> Double) -> (Double, Double, Int)
but that is not correct.

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to