[Haskell-cafe] Rigid skolem type variable escaping scope
Lauri Alanko
la at iki.fi
Wed Aug 22 21:02:17 CEST 2012
Quoting "Matthew Steele" <mdsteele at alum.mit.edu>:
> {-# LANGUAGE Rank2Types #-}
>
> class FooClass a where ...
>
> foo :: (forall a. (FooClass a) => a -> Int) -> Bool
> foo fn = ...
> newtype IntFn a = IntFn (a -> Int)
>
> bar :: (forall a. (FooClass a) => IntFn a) -> Bool
> bar (IntFn fn) = foo fn
In case you hadn't yet discovered it, the solution here is to unpack
the IntFn a bit later in a context where the required type argument is
known:
bar ifn = foo (case ifn of IntFn fn -> fn)
Hope this helps.
Lauri
More information about the Haskell-Cafe
mailing list