[Newbie] Programming with MArray
José Romildo Malaquias
romildo@uber.com.br
Fri, 8 Feb 2002 18:35:14 -0200
--82I3+IH0IqGh5yIs
Content-Type: text/plain; charset=iso-8859-1
Content-Disposition: inline
Content-Transfer-Encoding: 8bit
Hello.
To learn how to program with muttable arrays in Haskell, I have done
a very simple program to sum two arrays. I am submitting it to this
group so that it can be reviewd and commented. I have not find
examples on how to program with muttable arrays.
I would like for instance to see comments on the way the
iteration over the array indices was done: using a list
of indices. I looked for a way of incrementting an
index, starting from the lower bound towards the upper
bound, but failed in finding it. Is there other ways of
iterating over the muttable array other then using
its list of indices?
Regards,
Romildo
--
Prof. José Romildo Malaquias Departamento de Computação
http://iceb.ufop.br/~romildo Universidade Federal de Ouro Preto
romildo@iceb.ufop.br Brasil
romildo@uber.com.br
--82I3+IH0IqGh5yIs
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="t.hs"
module Main where
import MArray
import ST
addArray :: (Ix ix, Num a) =>
STArray s ix a -> STArray s ix a -> STArray s ix a -> ST s ()
addArray v1 v2 v3
| b1 == b2 && b1 == b3 = mapM_ update (indices v1)
| otherwise = error "Bounds mismatch in addArray"
where
b1 = bounds v1
b2 = bounds v2
b3 = bounds v3
update i = do x1 <- readArray v1 i
x2 <- readArray v2 i
writeArray v3 i (x1 + x2)
testAddArray = do v1 <- newListArray (1,10) [0..10]
v2 <- newListArray (1,10) [1..10]
v3 <- newArray_ (1,10)
addArray v1 v2 v3
getElems v3
main = do xs <- stToIO testAddArray
print xs
--82I3+IH0IqGh5yIs--