[Haskell-cafe] Mutable arrays

Stefan O'Rear stefanor at cox.net
Sat Feb 2 12:28:15 EST 2008


On Sat, Feb 02, 2008 at 12:57:47PM +0000, Rodrigo Queiro wrote:
> This is my attempt at some nicer code:
> 
> maximum' (x:xs) = foldl' max x xs
> maximum' _ = undefined
> 
> modifyArray :: (MArray a e m, Ix i) => (e -> e) -> a i e -> m ()
> modifyArray fn arr = do
>     bounds <- getBounds arr
>     forM_ (range bounds) (modifyElement fn arr)
> 
> modifyElement :: (MArray a e m, Ix i) => (e -> e) -> a i e -> i -> m ()
> modifyElement fn arr i = do
>     x <- readArray arr i
>     writeArray arr i (fn x)
> 
> normalizeArray :: (MArray a e m, Ix i, Fractional e, Ord e) => a i e -> m ()
> normalizeArray arr = do
>     arr_elems <- getElems arr
>     let max_elem = maximum' arr_elems
>     modifyArray (/max_elem) arr

Note that by using getElems, you are throwing away most of the
advantages of arrays, since it is strict (it has to be, since it's
effectively an IO function and lazy IO is unsound wrt Haskell's normal
semantics) and converts the whole thing into a list.

If I just had this one bit of code to do, I'd use explicit loop:

normalizeArray arr = do b <- getBounds arr ; m <- findMax b
                        forM_ (range b) (edit m)
  where
    findMax  (i:is)    = findMax' is         =<< readArray arr i
    findMax' (i:is) !v = findMax' is . max v =<< readArray arr i
    findMax' []     !v = return v

    edit mx i = writeArray arr i . (/mx) =<< readArray arr i

With a little more, I'd probably set the scene with a few
array-modifying combinators, inspired by Oleg's left-fold idea:

-- yes, I'm passing four arguments to foldr.  this is not a mistake.
foldA fn ac arr = getBounds arr >>= \b ->
                  foldr (\ i ct acc -> ct =<< fn i ac =<< readArray arr i)
                        (\_ -> return ac) (range b) ac

foldAp fn = foldA (\i a b -> return (fn a b))

maxA = foldAp max minBound
mapA fn ar = foldA (\i _ v -> writeArray ar i (fn v)) () ar

normalize arr = maxA arr >>= \ m -> mapA (/m) arr

Stefan
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080202/847dfb44/attachment.bin


More information about the Haskell-Cafe mailing list