[Haskell-cafe] Question on rank-N polymorphism

Ryan Ingram ryani.spam at gmail.com
Sun Jun 7 16:06:26 EDT 2009


The most interesting example is

fs ($ (1, "2"))

Which I haven't been able to make typecheck.

Here's some well-typed code:

> fs2 f g = (f fst, g snd)
> ab f = f ('a', "b")
> test = fs2 ab ab
> -- test2 = fs ab

The question is, is it possible to write fs such that your examples
typecheck and test2 also typechecks?

I find this example interesting because it's the smallest example I've
seen of a well-typed program which would "just work" in Scheme or
Lisp, but which we can't assign a type to in Haskell.

  -- ryan

On Sun, Jun 7, 2009 at 9:20 AM, Wouter Swierstra<wss at cs.nott.ac.uk> wrote:
>> The idea is that fs accepts a polymorphic function as its argument.
>> What type signature can I specify for f in order to compile this code?
>
> As you said yourself, you need to add a type signature to fs:
>
>> {-# LANGUAGE RankNTypes #-}
>>
>
>> fs :: ((forall a . ((a, a) -> a)) -> t) -> (t, t)
>> fs g = (g fst, g snd)
>>
>> examples = (fs id, fs repeat, fs (\x -> [x]), fs ((,)id))
>
>
> Hope this helps,
>
>  Wouter
>
>
> This message has been checked for viruses but the contents of an attachment
> may still contain software viruses, which could damage your computer system:
> you are advised to perform your own checks. Email communications with the
> University of Nottingham may be monitored as permitted by UK legislation.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list