
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. *****************************************************************

Bayley, Alistair wrote:
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),
This is probably completely off-topic, but you might also be interested in looking at diff arrays... http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Array.Diff.h... Diff arrays have an immutable interface, but rely on internal updates in place to provide fast functional update operator //. When the // operator is applied to a diff array, its contents are physically updated in place. The old array silently changes its representation without changing the visible behavior: it stores a link to the new current array along with the difference to be applied to get the old contents. So if a diff array is used in a single-threaded style, i.e. after // application the old version is no longer used, a'!'i takes O(1) time and a // d takes O(length d). Accessing elements of older versions gradually becomes slower. Greg Buchholz

Greg Buchholz
Diff arrays have an immutable interface, but rely on internal updates in place to provide fast functional update operator //.
While a cool concept, ISTR that somebody benchmarked these some time ago, and found the performance to be fairly poor in practice. Has that changed lately, or am I just misremembering? -k -- If I haven't seen further, it is by standing in the footprints of giants

On 8/25/05, Bayley, Alistair
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.
I think you should use runSTArray, return the array inside that epression, and then take the resulting Array and finding the element you want. runSTArray doesn't actually copy the STArray to a regular array, it just freezes it. So there's really no performance hit to get the immutable array as a result. Like so: compute :: Int -> Int compute n = runSTArray ( do arr <- newArray (-1, 1) n return arr ) ! 1 /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Bayley, Alistair wrote:
compute :: Int -> Int compute n = runST ( do arr <- newArray (-1, 1) n readArray 1 arr )
You messed the argument order to readArray up. Even with that repaired, you'll need a type signature somewhere to help ghc resolve the overloading of newArray and readArray, which is surprisingly tricky due to the "s" that must not escape. This works: compute :: Int -> Int compute n = runST ( do arr <- newArray (-1, 1) n :: ST s (STArray s Int Int) readArray arr 1 ) Udo. -- Mikrosoft spel chekar four sail, wurks grate!

Udo Stenzel
You messed the argument order to readArray up. Even with that repaired, you'll need a type signature somewhere to help ghc resolve the overloading of newArray and readArray, which is surprisingly tricky due to the "s" that must not escape.
I have struggled with this in the past, perhaps there is room for improvement in GHC's error messages? Instead of just talking about 's escaping', perhaps it could hint that a specific type declaration is what is needed? -k -- If I haven't seen further, it is by standing in the footprints of giants

On Thursday 25 August 2005 19:58, Udo Stenzel wrote:
[...] you'll need a type signature somewhere to help ghc resolve the overloading of newArray and readArray, which is surprisingly tricky due to the "s" that must not escape. This works:
compute :: Int -> Int compute n = runST ( do arr <- newArray (-1, 1) n :: ST s (STArray s Int Int) readArray arr 1 )
Hello, I am fighting with a similar problem. I want to use STUArray but without committing to a fixed element type. For instance, here is a function that appends two UArrays: A little helper first
copy :: (MArray a e m, IArray b e) => a Int e -> Int -> b Int e -> Int -> Int -> m () copy dest destix src srcix cnt | cnt <= 0 = return () | otherwise = do writeArray dest destix (src ! srcix) copy dest (destix+1) src (srcix+1) (cnt-1)
and here is the append function
append :: UArray Int e -> UArray Int e -> Int -> UArray Int e append x y low = runSTUArray (do z <- newArray_ (low,low+len x+len y) copy z low x (first x) (len x) copy z (low+len x) y (first y) (len y) return z) where len = rangeSize . bounds first = fst . bounds
Of course this can't work, because 'copy' needs the MArray and IArray contexts: No instance for (MArray (STUArray s) e (ST s)) arising from use of `copy' at Problem.lhs:31:7-10 [...] No instance for (IArray UArray e) arising from use of `copy' at Problem.lhs:31:7-10 [...] But now, when I add
append :: (IArray UArray e, MArray (STUArray s) e (ST s)) => ...
I still get the same error message regarding the MArray constraint: No instance for (MArray (STUArray s) e (ST s)) arising from use of `copy' at Problem.lhs:31:7-10 What am I missing? Ben

Benjamin Franksen wrote:
append :: (IArray UArray e, MArray (STUArray s) e (ST s)) => ...
I believe there must be an MArray instance for every s for this to work. If I understand types correctly (which isn't all that certain), the correct context would be
append :: (IArray UArray e, forall s . MArray (STUArray s) e (ST s)) => ...
which is illegal. A workaround might be possible by introducing a new class which doesn't need to mention s in the context. I can't see the solution, though. Udo. -- Uncle Ed's Rule of Thumb: Never use your thumb for a rule. You'll either hit it with a hammer or get a splinter in it.

Hi, There are also STArray examples on the wiki at http://haskell.org/hawiki/ImperativeHaskell This includes a very high performance use of STUArray example (from Autrijus), and a ST.Lazy example that I wrote that uses STArray. -- Chris

There are also STArray examples on the wiki at http://haskell.org/hawiki/ImperativeHaskell
This includes a very high performance use of STUArray example (from Autrijus), and a ST.Lazy example that I wrote that uses STArray.
Thanks. I saw these, but couldn't quite figure out what I needed to do for my program. I might add a note about helping the type-checker with the array type overloading. BTW, the STArray version of my code is honkin' fast (well, compared to the immutable array versions). And memory usage is way down, too.

Alistair Bayley wrote:
There are also STArray examples on the wiki at http://haskell.org/hawiki/ImperativeHaskell
This includes a very high performance use of STUArray example (from Autrijus), and a ST.Lazy example that I wrote that uses STArray.
Thanks. I saw these, but couldn't quite figure out what I needed to do for my program. I might add a note about helping the type-checker with the array type overloading.
BTW, the STArray version of my code is honkin' fast (well, compared to the immutable array versions). And memory usage is way down, too.
I made the Lazy example after almost two hours of trial and error with very very short functions until discovered how to get it correct and add type annotations. The difficulty is that ST uses an advanced type system trick to do what other languages do automatically: provide scope. In C++ any pair of braces works. In Haskell the scope is not well defined since you can compose many ST monad pieces into a final computation that runST or runST(U)Array calls. This is flexible, but the type annotation becomes unnatural, and the error messages make C++ template error reporting look clear by comparison. Mixing ST.Strict and ST.Lazy was the hardest bit to figure out since there was no Data.Array.ST.Lazy. Does anyone know why it was left out? I'll put a note on the HaskellTwo page about that... The odd thing is that there is not a "Haskell Array Tutorial" among all the other documentation. -- Chris

On Fri, Aug 26, 2005 at 08:27:43PM -0400, ChrisK wrote:
to figure out since there was no Data.Array.ST.Lazy. Does anyone know why it was left out? I'll put a note on the HaskellTwo page about that...
Some time ago when I wanted a lazy hashtable I came up with this, which, after minimal testing, seemed to work: (Lazy STRef's are implemented in exactly the same way, btw) \begin{code} {-# OPTIONS -fglasgow-exts #-} module MArrayLazyST ( STArray, module Data.Array.MArray ) where import Control.Monad.ST.Lazy import Data.Array.Base import Data.Array.ST import Data.Array.MArray instance MArray (STArray s) e (ST s) where newArray range e = strictToLazyST (newArray range e) newArray_ range = strictToLazyST (newArray_ range) unsafeRead arr i = strictToLazyST (unsafeRead arr i) unsafeWrite arr i e = strictToLazyST (unsafeWrite arr i e) \end{code} Cheers, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

On Fri, Aug 26, 2005 at 08:27:43PM -0400, ChrisK wrote:
This is flexible, but the type annotation becomes unnatural, and the error messages make C++ template error reporting look clear by comparison.
Are you getting 2MB long error messages from GHC? ;-> Best regards Tomasz
participants (10)
-
Alistair Bayley
-
Bayley, Alistair
-
Benjamin Franksen
-
ChrisK
-
Greg Buchholz
-
Ketil Malde
-
Remi Turk
-
Sebastian Sylvan
-
Tomasz Zielonka
-
Udo Stenzel