ghc optimization of incremental update

Simon Marlow simonmar at microsoft.com
Tue Jan 13 11:10:41 EST 2004


 
> Does ghc make any attempt to analyze dataflow and eliminate 
> unnecessary
> copying for incremental updates?  I compile the code below 
> with -O, and
> based on the time it takes to run I'd guess it's copying the 
> array with
> every update, even though there's no need in this particular 
> case to do
> that.  Perhaps there's a compiler flag or pragma to turn on 
> the analysis?
> 
> 	module Main where
> 	import Array
> 	main = print (take 1 (reverse (elems (array_neg (setup 
> 100000)))))
> 	setup i = listArray (1,i) [1..i]
> 	-- the next three lines are the important part.
> 	array_neg array = array_neg2 (length (elems array)) array
> 	array_neg2 0 array = array
> 	array_neg2 i array = array_neg2 (i-1) (array // [(i,-i)])
> 
> I realize I can force it to stop copying if I use a Monad, and there
> are of course more efficient ways to code this contrived testcase.
> I want to know if ghc can make it efficient as it stands.

GHC doesn't do this kind of optimisation, no.  There is the DiffArray
type which provides constant-time array update, although it has been
reported to have a high constant factor overhead.  Your best bet for
algorithms using mutable arrays is to encapsulate it in a state thread
with the ST monad.

Cheers,
	Simon


More information about the Haskell-Cafe mailing list