Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Why does this equivalent program not compile?

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?

like image 674
MaiaVictor Avatar asked Sep 05 '15 20:09

MaiaVictor


People also ask

What does it mean when code does not compile?

A compile error happens when the compiler reports something wrong with your program, and does not produce a machine-language translation.

Why does Python not compile?

Compiled bytecode, which is ran through an interpreter because Python is an interpreted language. Python is a compiled language. It just isn't compiled to a language for which a hardware implementation exists; it is executed by a virtual machine.

What causes a compilation error?

Compilation error refers to a state when a compiler fails to compile a piece of computer program source code, either due to errors in the code, or, more unusually, due to errors in the compiler itself. A compilation error message often helps programmers debugging the source code.

Why is JavaScript not compiled?

JavaScript is an interpreted language, not a compiled language. A program such as C++ or Java needs to be compiled before it is run. The source code is passed through a program called a compiler, which translates it into bytecode that the machine understands and can execute.


2 Answers

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.

like image 182
Zeta Avatar answered Sep 23 '22 21:09

Zeta


(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.

like image 33
chi Avatar answered Sep 26 '22 21:09

chi