Trying to use more than one array in runSTUArray

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 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 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) 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? Thanks in advance, 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@lsi.uji.es

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

On Thursday 15 March 2012, 19:53:56, Daniel Fischer wrote:
On Thursday 15 March 2012, 19:27:18, Juan Miguel Vilar wrote:
Hello, café:
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 #-}
Hmm, what compiler version are you using? When I actually tried to compile that, it failed with No instance for (MArray a0 Int (ST s)) without language extensions. After enabling MonoLocalBinds, however, it compiled with 6.12.3, 7.0.2, 7.0.4, 7.2.1 and 7.2.2, but 7.4.1 still refused to compile it.
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.

El 15/03/12 20:07, Daniel Fischer escribió:
On Thursday 15 March 2012, 19:53:56, Daniel Fischer wrote:
On Thursday 15 March 2012, 19:27:18, Juan Miguel Vilar wrote:
Hello, café:
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 #-}
Hmm, what compiler version are you using? When I actually tried to compile that, it failed with
No instance for (MArray a0 Int (ST s))
without language extensions. After enabling MonoLocalBinds, however, it compiled with 6.12.3, 7.0.2, 7.0.4, 7.2.1 and 7.2.2, but 7.4.1 still refused to compile it.
I am using 7.0.3. Adding type signatures solved the problems. And with respect to MonoLocalBinds, it failed after adding NoMonoLocalBinds, without it, everything went fine. Thanks a lot, 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@lsi.uji.es

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

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@lsi.uji.es
participants (3)
-
Anthony Cowley
-
Daniel Fischer
-
Juan Miguel Vilar