Rank2Types has been an alias for RankNTypes for several years.

In theory, rank-2 types allow some things that aren't possible for general rank-N types (e.g. decidable typechecking). In practice, ghc does not and probably never will implement those as special cases for rank-2 types, so it no longer distinguishes them.

On Fri, Dec 29, 2017 at 10:31 AM, Jean-Marc Alliot <jm@alliot.org> wrote:
Yes, thanks, it's exactly the same question, and the same trick works, using:
{-# LANGUAGE RankNTypes #-}
and
get2 :: (forall s.ST s (STArray s Int Int)) -> Int -> Int

In fact, Rank-2 types are enough here, we don't need Rank-N types.
I suppose the ST Array module uses the Rank-N extension, so using them requires also enabling Rank-N.

Thanks again.


Le 29/12/2017 à 16:11, Baa a écrit :
Hello!

I found this -
https://mail.haskell.org/pipermail/haskell-cafe/2011-May/091622.html

I'm not sure is it helpful.

PS. As I understand, `get2` signature has own `forall s`, but `runST`
is `(forall s. ST s a) -> a` which "escapes" top `s`.

Somebody else? :)

===
Best regards, Paul

Hi,

This is my first post to this list so I apologize in advance if I
don't use it properly, or if my question is too simple or
inapropriate.

I come from the Caml world and I am quite new to Haskell (but not to
functional programming). I am currently trying to get the hang of
Haskell arrays. I have gone through regular arrays, IO Arrays and I
am now working with ST Arrays.

This is the problem I am currently stuck with. I write the following
code:

arr = newArray (-1, 1) 0 :: ST s (STArray s Int Int)
get :: Int -> Int
get i = runST (arr >>= (\b -> readArray b i))

Here everything is perfectly OK.

Now I want a more general version that could deal with any array like
arr. So I write:

get2 :: ST s (STArray s Int Int) -> Int -> Int
get2 tab i = runST (tab >>= (\b -> readArray b i))

And the compiler is clearly very upset by my code:

Couldn't match type ‘s’ with ‘s1’
        ‘s’ is a rigid type variable bound by
          the type signature for:
            get2 :: forall s. ST s (STArray s Int Int) -> Int -> Int
          at testst.hs:17:9
        ‘s1’ is a rigid type variable bound by
          a type expected by the context:
            forall s1. ST s1 Int
          at testst.hs:18:14
        Expected type: ST s1 Int
          Actual type: ST s Int
I am pretty sure that the compiler is right and I am wrong, but I
don't get why... Anyone could help?

Thanks


_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.


_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.



--
brandon s allbery kf8nh                               sine nomine associates
allbery.b@gmail.com                                  ballbery@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net