
Hello, I am trying to create STArray with newListArray like this: la x y = newListArray ((1,1),(x,y)) [(x'+y') | x' <- [1..x], y' <- [1..y]] – but it does not work: No instance for (MArray a Field m) I tried to define the type like this, but it would not work either: la :: Int -> Int -> STArray (Int,Int) Field It is obvious that I don't get the syntax of using it, so I will appreciate any suggestions. V. K.

Am Sonntag 21 Februar 2010 16:30:00 schrieb Vojtěch Knyttl:
Hello,
I am trying to create STArray with newListArray like this: la x y = newListArray ((1,1),(x,y)) [(x'+y') | x' <- [1..x], y' <- [1..y]]
– but it does not work: No instance for (MArray a Field m)
I tried to define the type like this, but it would not work either: la :: Int -> Int -> STArray (Int,Int) Field
STArrays have a "state parameter", newListArray ((1,1),(x,y)) [(x'+y') | x' <- [1 .. x], y' <- [1 .. y]] has type forall s. ST s (STArray s (Int,Int) Int) So la :: forall s. Int -> Int -> ST s (STArray s (Int,Int) Int) la x y = newListArray ((1,1),(x,y)) [(x'+y') | x' <- [1 .. x], y' <- [1 .. y]] You can use STArrays only in the ST monad, there you'd do something like runST (do arr <- la 23 25 use arr return result)
It is obvious that I don't get the syntax of using it, so I will appreciate any suggestions.
V. K.

2010/2/21 Vojtěch Knyttl
Hello,
I am trying to create STArray with newListArray like this: la x y = newListArray ((1,1),(x,y)) [(x'+y') | x' <- [1..x], y' <- [1..y]]
– but it does not work: No instance for (MArray a Field m)
Notice that newListArray has a monadic return type: newListArray :: (MArray a e m, Ix i) => (i, i) -> [e] -> m (a i e) with MArray a e m requiring Monad m. So newListArray returns your STArray in a monad. That pretty much has to be the ST monad, but that's not in scope, so you need to import Control.Monad.ST before the MArray (STArray s) e (ST s) instance is usable.
I tried to define the type like this, but it would not work either: la :: Int -> Int -> STArray (Int,Int) Field
The kind for STArray here is slightly off. STArray needs three type parameters, not two. This is linked to the fact that ST is not a monad, but (ST s) is - the extra parameter is essential to ST, to ensure the mutability doesn't "leak out". You probably want: la :: Integer -> Integer -> ST s (STArray s (Integer, Integer) Field)

Ok, the problem was the Monad, which I still don't get completely, because I continue like this: data Field = W|B|H|D deriving (Eq,Show) pas :: ST s (STArray s (Int, Int) Field) -> ST s (STArray s (Int, Int) Field) pas b = do writeArray b (1,1) W And still getting: Couldn't match expected type `STArray s (Int, Int) Field' against inferred type `Field' Thanks. On Feb 21, 2010, at 5:33, Ben Millwood wrote:
2010/2/21 Vojtěch Knyttl
: Hello,
I am trying to create STArray with newListArray like this: la x y = newListArray ((1,1),(x,y)) [(x'+y') | x' <- [1..x], y' <- [1..y]]
– but it does not work: No instance for (MArray a Field m)
Notice that newListArray has a monadic return type:
newListArray :: (MArray a e m, Ix i) => (i, i) -> [e] -> m (a i e)
with MArray a e m requiring Monad m. So newListArray returns your STArray in a monad. That pretty much has to be the ST monad, but that's not in scope, so you need to import Control.Monad.ST before the MArray (STArray s) e (ST s) instance is usable.
I tried to define the type like this, but it would not work either: la :: Int -> Int -> STArray (Int,Int) Field
The kind for STArray here is slightly off. STArray needs three type parameters, not two. This is linked to the fact that ST is not a monad, but (ST s) is - the extra parameter is essential to ST, to ensure the mutability doesn't "leak out". You probably want:
la :: Integer -> Integer -> ST s (STArray s (Integer, Integer) Field)

Am Sonntag 21 Februar 2010 21:26:31 schrieb Vojtěch Knyttl:
Ok, the problem was the Monad, which I still don't get completely, because I continue like this:
data Field = W|B|H|D deriving (Eq,Show)
pas :: ST s (STArray s (Int, Int) Field) -> ST s (STArray s (Int, Int) Field) pas b = do writeArray b (1,1) W
Here, b has type (STArray s (Int,Int) Field), and writeArray has type ghci> :t writeArray writeArray :: (MArray a e m, Ix i) => a i e -> i -> e -> m () , in this case (STArray s (Int,Int) Field -> (Int,Int) -> Field -> ST s (), so the signature ought to be pas :: STArray s (Int,Int) Field -> ST s () It's new[List]Array, readArray, writeArray etc which have a type of ... -> ST s something the array itself doesn't.
And still getting: Couldn't match expected type `STArray s (Int, Int) Field' against inferred type `Field'
That's puzzling. I'd expect a different error message.
Thanks.
participants (3)
-
Ben Millwood
-
Daniel Fischer
-
Vojtěch Knyttl