[Haskell-cafe] How to use STArray?

Bayley, Alistair Alistair_Bayley at ldn.invesco.com
Thu Aug 25 11:29:03 EDT 2005


Hello all,

I have a pure function which uses immutable arrays from Data.Array, but it
spends about 95% of its time doing array updates. The arrays are used in a
single-threaded manner (no need for the old values after an array update),
and the arrays are not returned; just one of the elements. So I want to
convert it to use STArray, to see if there's a performance gain, but it's
not clear how I should tie everything together. I'm believe I don't want to
use runSTArray, because I'm not interested in getting an array back from the
pure function - just one of the elements.


Here's an contrived example:

module Main where
import Data.Array.ST
import Control.Monad.ST

main = print (compute 5)

compute :: Int -> Int
compute n = runST ( do
    arr <- newArray (-1, 1) n
    readArray 1 arr
  )


to which GHC responds: 

    No instance for (MArray a Int (ST s))
      arising from use of `readArray' at test.hs:11:4-12
    Probable fix:
      add (MArray a Int (ST s)) to the expected type of an expression
      or add an instance declaration for (MArray a Int (ST s))
    In the result of a 'do' expression: readArray 1 arr
    In the first argument of `runST', namely
        `(do
            arr <- newArray (- 1, 1) n
            readArray 1 arr)'
    In the definition of `compute':
        compute n = runST (do
                             arr <- newArray (- 1, 1) n
                             readArray 1 arr)


Alistair

-----------------------------------------
*****************************************************************
Confidentiality Note: The information contained in this   message, and any
attachments, may contain confidential   and/or privileged material. It is
intended solely for the   person(s) or entity to which it is addressed. Any
review,   retransmission, dissemination, or taking of any action in
reliance upon this information by persons or entities other   than the
intended recipient(s) is prohibited. If you received  this in error, please
contact the sender and delete the   material from any computer.
*****************************************************************



More information about the Haskell-Cafe mailing list