<div dir="ltr">Rank2Types has been an alias for RankNTypes for several years.<div><br><div>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.</div></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Fri, Dec 29, 2017 at 10:31 AM, Jean-Marc Alliot <span dir="ltr"><<a href="mailto:jm@alliot.org" target="_blank">jm@alliot.org</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Yes, thanks, it's exactly the same question, and the same trick works, using:<br>
{-# LANGUAGE RankNTypes #-}<br>
and<br>
get2 :: (forall s.ST s (STArray s Int Int)) -> Int -> Int<br>
<br>
In fact, Rank-2 types are enough here, we don't need Rank-N types.<br>
I suppose the ST Array module uses the Rank-N extension, so using them requires also enabling Rank-N.<br>
<br>
Thanks again.<div class="HOEnZb"><div class="h5"><br>
<br>
Le 29/12/2017 à 16:11, Baa a écrit :<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
Hello!<br>
<br>
I found this -<br>
<a href="https://mail.haskell.org/pipermail/haskell-cafe/2011-May/091622.html" rel="noreferrer" target="_blank">https://mail.haskell.org/piper<wbr>mail/haskell-cafe/2011-May/<wbr>091622.html</a><br>
<br>
I'm not sure is it helpful.<br>
<br>
PS. As I understand, `get2` signature has own `forall s`, but `runST`<br>
is `(forall s. ST s a) -> a` which "escapes" top `s`.<br>
<br>
Somebody else? :)<br>
<br>
===<br>
Best regards, Paul<br>
<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
Hi,<br>
<br>
This is my first post to this list so I apologize in advance if I<br>
don't use it properly, or if my question is too simple or<br>
inapropriate.<br>
<br>
I come from the Caml world and I am quite new to Haskell (but not to<br>
functional programming). I am currently trying to get the hang of<br>
Haskell arrays. I have gone through regular arrays, IO Arrays and I<br>
am now working with ST Arrays.<br>
<br>
This is the problem I am currently stuck with. I write the following<br>
code:<br>
<br>
arr = newArray (-1, 1) 0 :: ST s (STArray s Int Int)<br>
get :: Int -> Int<br>
get i = runST (arr >>= (\b -> readArray b i))<br>
<br>
Here everything is perfectly OK.<br>
<br>
Now I want a more general version that could deal with any array like<br>
arr. So I write:<br>
<br>
get2 :: ST s (STArray s Int Int) -> Int -> Int<br>
get2 tab i = runST (tab >>= (\b -> readArray b i))<br>
<br>
And the compiler is clearly very upset by my code:<br>
<br>
Couldn't match type ‘s’ with ‘s1’<br>
        ‘s’ is a rigid type variable bound by<br>
          the type signature for:<br>
            get2 :: forall s. ST s (STArray s Int Int) -> Int -> Int<br>
          at testst.hs:17:9<br>
        ‘s1’ is a rigid type variable bound by<br>
          a type expected by the context:<br>
            forall s1. ST s1 Int<br>
          at testst.hs:18:14<br>
        Expected type: ST s1 Int<br>
          Actual type: ST s Int<br>
I am pretty sure that the compiler is right and I am wrong, but I<br>
don't get why... Anyone could help?<br>
<br>
Thanks<br>
<br>
<br>
______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/haskell-caf<wbr>e</a><br>
Only members subscribed via the mailman list are allowed to post.<br>
</blockquote>
______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/haskell-caf<wbr>e</a><br>
Only members subscribed via the mailman list are allowed to post.<br>
</blockquote>
<br>
<br>
______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/haskell-caf<wbr>e</a><br>
Only members subscribed via the mailman list are allowed to post.</div></div></blockquote></div><br><br clear="all"><div><br></div>-- <br><div class="gmail_signature" data-smartmail="gmail_signature"><div dir="ltr"><div>brandon s allbery kf8nh                               sine nomine associates</div><div><a href="mailto:allbery.b@gmail.com" target="_blank">allbery.b@gmail.com</a>                                  <a href="mailto:ballbery@sinenomine.net" target="_blank">ballbery@sinenomine.net</a></div><div>unix, openafs, kerberos, infrastructure, xmonad        <a href="http://sinenomine.net" target="_blank">http://sinenomine.net</a></div></div></div>
</div>