
On Thursday 15 March 2012, 19:27:18, 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.
The compiler can infer the type of b (STUArray s Integer Int), since that is returned (and then frozen to a UArray Integer Int), but it cannot infer what array type to use for a. Thus that function does not compile.
However, when I write
test2 n = runSTUArray $ do let createArray v n = newArray (1, n) (v::Int)
Here you create a local binding for createArray that gets a monomorphic type, that type is the fixed by the returning of b to createArray :: Int -> Integer -> ST s (STUArray s Integer Int) you can make that fail too with enabling {-# LANGUAGE NoMonoLocalBinds #-}
a <- createArray 2 n b <- createArray 0 n forM_ [1..n] $ \i -> do v <- readArray a i writeArray b i (v+1) return b
everything is fine although I expected the two versions to be equivalent. To further complicate matters, the following
createArray v n = newArray (1, n) (v::Int)
This is a top-level definition, createArray is bound by a function binding, hence it is polymorphic again, and as in the first case, the type of a cannot be inferred. Give it a type signature createArray :: Int -> Int -> ST s (STUArray s Int Int) (I chose Int for the indices here instead of the default Integer)
test3 n = runSTUArray $ do a <- createArray 2 n b <- createArray 3 n forM_ [1..n] $ \i -> do v <- readArray a i writeArray b i (v+1) return b
does not work either. Where can I find an explanation for this behaviour? Furthermore, what I am after is to use two arrays with different types (Int and Bool), is it possible?
Sure, you need to use type signatures. With expression type signatures, it would look like test1 n = runSTUArray $ do a <- newArray (1, n) 2 :: ST s (STUArray s Int Int) b <- newArray (1, n) 3 :: ST s (STUArray s Int Int) forM_ [1..n] $ \i -> do v <- readArray a i writeArray b i (v+1) return b If you don't want to give expression type signatures at every use, you can create a top-level function {-# LANGUAGE FlexibleContexts #-} createArray :: (Marray (STUArray s) a (ST s)) => a -> Int -> ST s (STUArray s Int a) createArray v n = newArray (1,n) v and you have to deal with only one type signature.
Thanks in advance,
Juan Miguel