[Haskell] Help in understanding a type error involving forall and class constraints

Duncan Coutts duncan.coutts at worcester.oxford.ac.uk
Tue Jun 29 13:22:19 EDT 2004


Here's a small bit of code that involves some fairly hairy class
overloadings (ghc's mutable unboxed array classes)

The code builds an array in the ST monad by creating a mutable array
then assigning to each element and finally freezing the array and
returning an immutable array.

Firstly the bit that does most of the work (in the ST monad). We have a
MArray class constraint because we're working generically on any mutable
unboxed array. Its not completely generic however since we know we're
working in the ST monad with unboxed ST arrays 'STUArray'.

buildUArray' :: (Ix i, MArray (STUArray s) a (ST s)) =>
                (i,i) -> (i -> a) -> ST s (STUArray s i a)
buildUArray' bounds f = do
  arr <- newArray_ bounds
  mapM_ (\i -> writeArray arr i (f i)) (range bounds)
  return arr

Now the wrapper which freezes the mutable array and gives us back an
immutable array (still in the ST monad). We gain an extra IArray class
constraint.

buildUArray :: (MArray (STUArray s) a (ST s), Ix i, IArray UArray a) =>
	       (i, i) -> (i -> a) -> ST s (UArray i a)
buildUArray bounds f = do arr <- buildUArray' bounds f
                          unsafeFreeze arr

This all typechecks fine. Now lastly we want to run this state thread
monad to get the resultant 'UArray i a'

foo :: (MArray (STUArray s) a (ST s), Ix i, IArray UArray a) =>
       (i, i) -> (i -> a) -> UArray i a
foo bounds f = runST (buildUArray bounds f)

At first this seems like it ought to be the right type (it does discard
the 's' type), but ghc complains:

No instance for (MArray (STUArray s) a (ST s))
      arising from use of `buildUArray' at BuildArray.hs:25:22-32
    Probable fix:
      Add (MArray (STUArray s) a (ST s)) to the expected type of an expression
      Or add an instance declaration for (MArray (STUArray s) a (ST s))
    In the first argument of `runST', namely `(buildUArray bounds f)'
    In the definition of `foo': foo bounds f = runST (buildUArray bounds f)

I get the same error if I leave off the type signature for 'foo'. The
error message suggests I add a class constraint that I've already added.
I suspect there's a name clash and the 's' it means is not the same as
the 's' that I've already got.

Anyone have an idea what's wrong? My guess is that it's related to the
nested forall type of runST. We need to express a class constraint on a
type that is universally quantified but that doesn't escape to the top
level of the functions type. If this is the case, it doesn't do any good
to add the 'MArray (STUArray s) a (ST s)' constraint because 's' does
not exist at this level of type scope (it just introduces a shadowing). 
So how would I write a constraint that involves 's'?

Duncan


Ps. similar code that uses normal (not unboxed) arrays works fine, but
is has less complicated class constraints:

buildArray :: Ix i => (i,i) -> (i -> a) -> Array i a
buildArray bounds f = runST (do arr <- buildArray' bounds f
                                unsafeFreeze arr)
  where buildArray' :: Ix i => (i,i) -> (i -> a) -> ST s (STArray s i a)
        buildArray' bounds f = do
          arr <- newArray_ bounds
          mapM_ (\i -> writeArray arr i (f i)) (range bounds)
          return arr



More information about the Haskell mailing list