[Haskell-beginners] Type problems with IOArray

Xuan Luo spoon.reloaded at gmail.com
Wed Oct 22 22:26:15 EDT 2008


I am having lots of trouble using polymorphic mutable IOArrays. Here
is an example program:

import Data.Array.MArray
import Data.Array.IO

foo x = do a <- newArray (0, 4) x
           readArray a 2

main = foo 42 >>= print

So there is a function "foo" which makes an array of polymorphic type
initialized with a value, then returns one of the elements of the
array. So here "foo x" essentially does the same as "return x"; but it
demonstrates problems I am having.

So the above program fails with:
testarray.hs:7:7:
    No instance for (MArray a t IO)
      arising from a use of `foo' at testarray.hs:7:7-12
    Possible fix: add an instance declaration for (MArray a t IO)
    In the first argument of `(>>=)', namely `foo 42'
    In the expression: foo 42 >>= print
    In the definition of `main': main = foo 42 >>= print

Okay; so the problem is that "newArray" is a function that creates
MArrays in general; but there is no function to specifically create
IOArrays in particular, and it doesn't know I want to use IOArrays. In
fact, all the other functions that are used to operate on mutable
arrays are generic MArray functions too, and there is basically
nothing that is specific to IOArrays, so it is not as if the compiler
can "figure it out from context". This is bad design. I wish it could
just decide to default to IOArrays or something, since IOArrays of any
type already are instances of MArray, so it would be natural.

Okay so the general way to resolve this is to add signatures to tell
it that it is an IOArray. But when I give the type for IOArray I also
have to tell it what type its contents are, and I want it to work
polymorphically over any type, so the array has to be of a polymorphic
type:

foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

But of course it doesn't know what "a" is, so maybe I am forced to
also add a signature for the function "foo" itself, which the compiler
should really be able to figure out for me:

import Data.Array.MArray
import Data.Array.IO

foo :: a -> IO a
foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

main = foo 42 >>= print

Okay, now the real problems begin:
testarray.hs:5:32:
    Couldn't match expected type `a1' against inferred type `a'
      `a1' is a rigid type variable bound by
           the polymorphic type `forall a1. IO (IOArray Int a1)'
             at testarray.hs:5:16
      `a' is a rigid type variable bound by
          the type signature for `foo' at testarray.hs:4:7
    In the second argument of `newArray', namely `x'
    In a 'do' expression: a <- newArray (0, 4) x :: IO (IOArray Int a)
    In the expression:
        do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

What the heck is this? I looked through a lot of stuff online and
eventually found that this works:

{-# LANGUAGE ScopedTypeVariables #-}
import Data.Array.MArray
import Data.Array.IO

foo :: forall a. a -> IO a
foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

main = foo 42 >>= print

So I had to add some weird "forall" stuff to my function signature and
enable some language extension flag(?). This seems way too
complicated.

I just want to be able to make and use a simple polymorphic array in
the IO monad with regular Haskell, without changing compiler flags or
anything like that. I have been doing well in other stuff involving
the IO monad, but these mutable arrays really got me stuck.

Thanks,


More information about the Beginners mailing list