[Haskell-cafe] Trying to use more than one array in runSTUArray

Juan Miguel Vilar jvilar at uji.es
Thu Mar 15 23:51:07 CET 2012


El 15/03/12 19:53, Anthony Cowley escribió:
> On Thursday, March 15, 2012 at 2:27 PM, Juan Miguel Vilar wrote:
>> Hello, café:
>>
>> I am trying to use more than one array with runSTUArray but I don't seem
>> to be able to understand how it works. My first try is this:
>>
>> test1 n = runSTUArray $ do
>> a <- newArray (1, n) (2::Int)
>> b <- newArray (1, n) (3::Int)
>> forM_ [1..n] $ \i -> do
>> v <- readArray a i
>> writeArray b i (v+1)
>> return b
>>
>> but it does not work. However, when I write
>
> The problem is that GHC doesn't know what type of array a is. If you
> provide an annotation, you can resolve the ambiguity:
>
> a <- newArray (1,n) (2::Int) :: ST s (STUArray s Int Int)
>
> However, this is somewhat ugly, so we should look at your next example:
>>
>> test2 n = runSTUArray $ do
>> let createArray v n = newArray (1, n) (v::Int)
>> a <- createArray 2 n
>> b <- createArray 0 n
>> forM_ [1..n] $ \i -> do
>> v <- readArray a i
>> writeArray b i (v+1)
>> return b
>
> Note that the type of the b array was never in doubt thanks to
> runSTUArray. What you've done here is said that the same function that
> creates b also creates a, and since we know b's type, we now know a's
> type because GHC doesn't make createArray's type as polymorphic as it might.
>
> Another approach to resolving the types is to essentially do what you've
> done in your second example, but give createArray a type that is as
> polymorphic as you need:
>
> {-# LANGUAGE FlexibleContexts #-}
>
> newSTUArray :: (MArray (STUArray s) e (ST s), Ix i) =>
> (i,i) -> e -> ST s (STUArray s i e)
> newSTUArray = newArray
>
> test3 n = runSTUArray $ do
> a <- newSTUArray (1, n) False
> b <- newSTUArray (1, n) (3::Int)
> forM_ [1..n] $ \i -> do
> v <- readArray a i
> writeArray b i (fromEnum v+1)
> return b
>
> I hope that helps clear things up. The issue to be aware of,
> particularly with the Array types, is just how polymorphic the
> interfaces you rely upon are. The best approach to figuring these
> problems out is to add type annotations to see where your intuition
> diverged from the type checker's reality.
>
> Anthony

Thanks a lot, it is much clear now.

   Regards,

   Juan Miguel

-- 
Juan Miguel Vilar Torres
Profesor titular de universidad
Vicedirector de la ESTCE para ITIG e ITIS
Departamento de Lenguajes y Sistemas Informáticos
Escuela Superior de Tecnología y Ciencias Experimentales
Universitat Jaume I
Av. de Vicent Sos Baynat s/n
12071 Castelló de la Plana (Spain)
Tel: +34 964 72 8365
Fax: +34 964 72 8435
jvilar at lsi.uji.es



More information about the Haskell-Cafe mailing list