List comprehensions and impredicative rank-N types
Vladimir Reshetnikov
v.reshetnikov at gmail.com
Thu Jun 11 11:00:41 EDT 2009
Hi,
Consider the following definitions:
-----------------------------------------------------------
{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}
foo :: [forall a. [a] -> [a]]
foo = [reverse]
bar :: [a -> b] -> a -> b
bar fs = head fs
-----------------------------------------------------------
According to the Haskell Report, [f | f <- foo] translates to (let ok
f = [f]; ok _ = [] in concatMap ok foo), right?
So, I wonder why (bar [f | f <- foo]) typechecks, but (bar (let ok f =
[f]; ok _ = [] in concatMap ok foo)) and (bar foo) do not typecheck?
Thanks,
Vladimir
More information about the Glasgow-haskell-users
mailing list