[Haskell-cafe] Re: Help in understanding a type error involving forall and class constraints

oleg at pobox.com oleg at pobox.com
Tue Jul 6 02:17:00 EDT 2004


>         Is it possible to return an arbitrary unboxed array that was
>         constructed in the ST monad (as an STUArray)?
        
>         The issue is that you end up with a MArray class constraint that
>         involves the state thread's 's' parameter, but this type
>         variable gets 'hidden' by runST which universally quantifies
>         over it.        runST :: forall a. (forall s. ST s a) -> a

That seems to be possible.

Let us start with the original code:

> buildUArray' bounds f = do
>   arr <- newArray_ bounds
>   mapM_ (\i -> writeArray arr i (f i)) (range bounds)
>   return arr
>
> buildUArray bounds f = do arr <- buildUArray' bounds f
>                           unsafeFreeze arr

If we check for the type of buildUArray

*Foo> :t buildUArray
buildUArray :: forall e a1 b m a.
	       (MArray a e m, Ix a1, IArray b e) =>
	       (a1, a1) -> (a1 -> e) -> m (b a1 e)

we see the problem. It is in the constraint MArray a e m. If we use
that function in runST, as in
	foo bounds f = runST (buildUArray bounds f)

the constraint 'MArray a e m' has to be provided by the function
foo. However, 'm' in that constraint will be 'ST s', so the state
variable escapes. Therefore, the typechecker rejects foo.

We should notice that the type variable 'a' in the above type appears
only in the constraint -- but not in the types. That is, 'a' will be
_existentially_ quantified. Thus, we can provide the needed constraint
via an explicit existential type. Here's the solution

> data Allocator m i e = forall a. MArray a e m => 
>                        Allocator ((i, i) -> m (a i e))
>
> buildUArray'' allocator bounds f = 
>   case allocator of
>     Allocator alloc -> do
>                         arr <- alloc bounds
> 			  mapM_ (\i -> writeArray arr i (f i)) (range bounds)
> 			  unsafeFreeze arr

*Foo> :t buildUArray''
buildUArray'' :: forall e a b m.
		 (Monad m, Ix a, IArray b e) =>
		 Allocator m a e -> (a, a) -> (a -> e) -> m (b a e)

That type shows that now buildUArray'' is truly polymorphic over the
array types; furthermore, the particular MArray type is irrelevant. As
we can see, the MArray constraint is nowhere to be found -- just as we
wanted to.

we can define one particular allocator, specifically for STUArray

> allc:: Ix i => Allocator (ST s) i Bool
> allc = Allocator (newArray_:: Ix i => (i,i) -> ST s (STUArray s i Bool))

we can then write

> foo bounds f = runST (buildUArray'' allc bounds f)
> test = foo (1::Int,2::Int) (const True) :: Array Int Bool

One can say that foo builds only arrays of Booleans. Can we have a
function that builds polymorphic arrays? The answer is again yes. We
merely need to make our allocator polymorphic with respect to the type
of the array:

> class STUGood e where
>     allcg::Ix i => Allocator (ST s) i e 

> instance STUGood Bool where
>     allcg = Allocator (newArray_:: Ix i => (i,i) -> ST s (STUArray s i Bool))

> instance STUGood Float where
>     allcg = Allocator (newArray_:: Ix i => (i,i)-> ST s (STUArray s i Float))

etc.

> bar bounds f = runST (buildUArray'' allcg bounds f)

*Foo> :t bar
bar :: forall e i b.
       (IArray b e, STUGood e, Ix i) =>
       (i, i) -> (i -> e) -> b i e

The type of bar is indeed polymorphic with respect to the index, the
sort of the array, and the type of the element of the array:

> test2 x :: Array Int x = bar (1::Int,2::Int) (const x)

*Foo> test2 (1.0::Float)
array (1,2) [(1,1.0),(2,1.0)]
*Foo> test2 True
array (1,2) [(1,True),(2,True)]

As we see, we indeed need to define instances of STUGood for Bool, Char,
Float, Word32, etc. One might wish if the designers of the Haskell
library introduced a class 'Unpackable'. In that case, we would have
needed only one STUArray instance
	instance Unpackable e => MArray (STUArray s) e (ST s)

The constraint Unpackable would have made solving your problem
easier. 

For the sake of completeness, I'd like to mention another solution,
using castSTUArray. Yet it smacks too much of dynamic typing...



More information about the Haskell-Cafe mailing list