8

This program:

{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

import qualified Data.Vector.Mutable as MV
import qualified Data.Vector as V
import Control.Monad.ST
import Control.Monad.Primitive

unsafeModify :: [(forall s . MV.MVector s Int -> ST s ())] -> V.Vector Int -> V.Vector Int
unsafeModify mods vec = runST $ do
    mvec <- V.unsafeThaw vec
    (mods !! 0) mvec
    V.unsafeFreeze mvec

Compiles. This program:

{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

import qualified Data.Vector.Mutable as MV
import qualified Data.Vector as V
import Control.Monad.ST
import Control.Monad.Primitive

unsafeModify :: [(forall s . MV.MVector s Int -> ST s ())] -> V.Vector Int -> V.Vector Int
unsafeModify mods vec = runST $ do
    mvec <- V.unsafeThaw vec
    ($ mvec) (mods !! 0)
    V.unsafeFreeze mvec

Does not compile with the following error:

Muts.hs:10:15:
    Couldn't match type ‘forall s1. UV.MVector s1 Int -> ST s1 ()’
                  with ‘UV.MVector s Int -> ST s a0’
    Expected type: [UV.MVector s Int -> ST s a0]
      Actual type: [forall s. UV.MVector s Int -> ST s ()]
    Relevant bindings include
      mvec :: UV.MVector s Int (bound at Muts.hs:9:5)
    In the first argument of ‘(!!)’, namely ‘mods’
    In the first argument of ‘$ mvec’, namely ‘(mods !! 0)’

Why?

jub0bs
  • 46,795
  • 22
  • 148
  • 157
MaiaVictor
  • 45,122
  • 42
  • 127
  • 254
  • What error does the second one give? – Silvio Mayolo Sep 05 '15 at 20:56
  • Question updated. Sorry. – MaiaVictor Sep 05 '15 at 20:57
  • 7
    Basically due to the `forall` Rank2Type in your list. `$` has the (explicit) type `forall a b. (a -> b) -> a -> b`, and `(a -> b)` isn't compatible to `forall s. MV.Vector s Int -> St s ()`. See [this article](https://www.fpcomplete.com/school/to-infinity-and-beyond/pick-of-the-week/guide-to-ghc-extensions/explicit-forall#rankntypes--rank2types--and-polymorphiccomponents) for a quick overview of RankNTypes. – Zeta Sep 05 '15 at 20:58
  • 4
    `ImpredicativeTypes` doesn't actually work. If GHC suggests using it, don't. – dfeuer Sep 05 '15 at 22:27

2 Answers2

3

Note: This post is written in literate Haskell. You can save it as Unsafe.lhs and try it in your GHCi.


Let's compare the types of the different lines:

 mods                ::     [(forall s . MV.MVector s Int -> ST s ())]
(mods !! 0)          ::      (forall s . MV.MVector s Int -> ST s ())
(mods !! 0)  mvec    ::       forall s. ST s ()


($ mvec)             ::     (MV.Vector s Int -> b) -> b
         (mods !! 0) ::     (forall s . MV.MVector s Int -> ST s ())
($ mvec) (mods !! 0) ::     ????????????????????????

They aren't equivalent due to $'s type:

($) :: forall a b. (a -> b) -> a -> b

Whereas you would need something along

($)  :: (a ~ (forall s . MV.MVector s Int -> ST s ())) =>
      (a -> b) -> a -> b

which isn't legal.

However, let's have a look at what you actually want to do.

> {-# LANGUAGE RankNTypes #-}

> import qualified Data.Vector.Mutable as MV
> import qualified Data.Vector as V
> import Control.Monad.ST
> import Control.Monad.Primitive

  unsafeModify :: ??? -> V.Vector Int -> V.Vector Int

> unsafeModify mods vec = runST $ do
>   mvec <- V.unsafeThaw vec
>   mapM_ ($ mvec) (mods !! 0)
>   V.unsafeFreeze mvec

Things got messy due to unsafeModify's polymorphic first argument mods. Your original type

[(forall s . MV.MVector s Int -> ST s ())]

tells us it is a list of functions, where every function is polymorphic the parameter s, so every function could use another s. However, that's too much. It's fine if the s gets shared throuhgout the whole list:

(forall s. [MV.MVector s Int -> ST s ()])

After all, we want to use all functions in the same ST computation, therefore the type of the stream state token s can be the same. We end up with

> unsafeModify :: (forall s. [MV.MVector s Int -> ST s ()]) -> V.Vector Int -> V.Vector Int

And now your code happily compiles, regardless of whether you use ($ mvec) (mods !! 0), (mods !! 0) mvec or mapM_, because s is now correctly fixed by runST throughout the whole list.

Zeta
  • 95,453
  • 12
  • 173
  • 214
  • The `????` part begs the question: why doesn't GHC instantiate the `s` in the polytype for `(mods !! 0)` to be the same as the (rigid) `s` in the type of `($ mvec)`? After all, when we do `(+) (length []) 10` the polytype of `10` gets instantiated correctly to `Int`. – chi Sep 06 '15 at 06:07
  • `$` gets its own special case in the type checker. – dfeuer Sep 06 '15 at 14:33
3

(This should probably be a comment, but I need more space.)

Sadly, impredicative types do not work very well in GHC, as @dfeuer pointed out. Consider this example:

{-# LANGUAGE ImpredicativeTypes, PartialTypeSignatures #-}
import qualified Data.Vector.Mutable as MV
import Control.Monad.ST

-- myIndex :: [forall s. MV.MVector s Int -> ST s ()] 
--         -> Int
--         -> (forall s. MV.MVector s Int -> ST s ())
myIndex = (!!) :: [forall s. MV.MVector s Int -> ST s ()] -> Int -> _

It compiles successfully, albeit with a warning due to the type hole:

VectorTest.hs:9:69: Warning:
    Found hole ‘_’ with type: forall s. MV.MVector s Int -> ST s ()
    Relevant bindings include
      myIndex :: [forall s. MV.MVector s Int -> ST s ()]
                 -> Int -> forall s. MV.MVector s Int -> ST s ()
        (bound at VectorTest.hs:9:1)

We could try to remove the PartialTypeSignatures extension and fill the hole with its type forall s. MV.MVector s Int -> ST s (). But this fails horribly:

VectorTest.hs:9:11:
    Couldn't match type ‘forall s2. MV.MVector s2 Int -> ST s2 ()’
                   with ‘MV.MVector s1 Int -> ST s1 ()’
    Expected type: [forall s. MV.MVector s Int -> ST s ()]
                   -> Int -> MV.MVector s1 Int -> ST s1 ()
      Actual type: [MV.MVector s1 Int -> ST s1 ()]
                   -> Int -> MV.MVector s1 Int -> ST s1 ()

The last forall gets hoisted to the top-level, and now GHC infers that the first argument of (!!) must a be a list of monomorphic elements [MV.MVector s1 Int -> ST s1 ()] despite our annotation! Basically, GHC has two choices:

-- Note the hoisted forall s1
myIndex = (!!) :: forall s1. [forall s. MV.MVector s Int -> ST s ()] -> Int 
               -- ^ first choice for instantiating the type of (!!)
               -> MV.MVector s1 Int -> ST s1 ()
               -- ^ second choice

GHC chooses the second, and fails. Only with a partial type signature I was able to remove the second choice so that GHC was forced to do the right thing.

If only we had explicit type application like in GHC Core, we could have written (!!) @ (forall s. ...), but alas we have not.

chi
  • 101,733
  • 3
  • 114
  • 189