The following code crashes when compiled with -O2. With -O it does
not crash. Some trivial modifications make the crash go away.
------------------------------------------------------------------------
import Array (Array, array, (!))
import Random (StdGen, newStdGen)
import MonadRWS (RWS(..), tell)
type M = RWS () ([((Int,Int),Float)] -> [((Int,Int),Float)]) StdGen
plot:: Int -> Int -> Float -> M ()
plot x y v = tell (((y,x), v):)
plasma:: Int -> Int -> StdGen -> Array (Int,Int) Float
plasma width height gen = a
where
plasma' = do
plot 0 0 0
subdivide 0 0 width height
(_,_,pixels) = runRWS plasma' () gen
a = array ((0,0), (height-1,width-1)) (pixels [])
subdivide x1 y1 x2 y2 = let
x = (x1+x2) `div` 2
y = (y1+y2) `div` 2
x2w = if x2==width then 0 else x2
y2w = if y2==height then 0 else y2
mid x1' y1' x' y' x2' y2' = do
plot x' y' ((a!(y1',x1')+a!(y2',x2'))/2)
cl = mid x1 y1 x1 y x1 y2w
uc = mid x1 y1 x y1 x2w y1
cc = plot x y 0
dr = subdivide x y x2 y2
dl = subdivide x1 y x y2
ur = subdivide x y1 x2 y
ul = subdivide x1 y1 x y
in sequence_ $ case (x2-x1, y2-y1) of
(1,1) -> []
(1,_) -> [cl]
(_,1) -> [uc,dr,dl]
(_,_) -> [cl,uc,cc,dr,dl,ur,ul]
main:: IO ()
main = do
gen <- newStdGen
print (plasma 1 2 gen)
------------------------------------------------------------------------
$ ghc -O2 -fglasgow-exts P.hs -o P
$ ./P
zsh: segmentation fault ./P
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 4.06
--
__("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
\__/ GCS/M d- s+:-- a22 C+++$ UL++>++++$ P+++ L++>++++$ E-
^^ W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK 5? X- R tv-- b+>++ DI D- G+ e>++++ h! r--%>++ y-