
On 10 March 2011 17:55, Bas van Dijk
On 10 March 2011 18:24, Yves Parès
wrote: Why has the operator (.) troubles with a type like (forall s. ST s a)?
Why can't it match the type 'b' in (.) definition?
As explained by the email from SPJ that I linked to, instantiating a type variable (like 'b') with a polymorphic type (like 'forall s. ST s a' ) is called impredicative polymorphism. Since GHC-7 this is not supported any more because it was to complicated.
AFAIK this decision was reversed because SPJ found a simple way to support them. Indeed, they work fine in 7.0.2 and generate warnings. Try it out: {{{ {-# LANGUAGE ImpredicativeTypes #-} module Impred where f :: Maybe (forall a. [a] -> [a]) -> Maybe ([Int], [Char]) f (Just g) = Just (g [3], g "hello") f Nothing = Nothing }}} Unfortunately, the latest user guide still reflects the old situation: http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extension... Cheers, Max