#3586: Initialisation of unboxed arrays is too slow
-----------------------------------------+----------------------------------
Reporter: simonpj | Owner:
Type: run-time performance bug | Status: new
Priority: high | Milestone: 6.12.2
Component: libraries (other) | Version: 6.10.4
Severity: normal | Resolution:
Keywords: | Difficulty: Unknown
Testcase: | Os: Unknown/Multiple
Architecture: Unknown/Multiple |
-----------------------------------------+----------------------------------
Comment (by Philippos):
I have a genetic programming code that I am trying to translate to
Haskell. I applied suggestions received here to a slightly more realistic
situation, where array ar contains a tree population. Function fn updates
the array randomly, in order to simulate crossover and mutation of
individuals of the population. The result seems to be very good, i.e.,
Haskell is from 3 to 5 times slower than Clean. I would rather not use
unsafe features. Therefore, I will appreciate if someone substitute
something else for (unsafePerformIO (randomList (1, 2000000))). I wonder
whether a member of this forum could make the gap between Clean and
Haskell even smaller. Here are the programs:
{{{
-- Haskell version
data Op = AND | OR | NOT;
data Tree= L Double | T Op [Tree]
main = print $ runST
(do arr <- newArray (1,2000000) (L 0.0) :: ST s (STArray s Int
Tree)
go arr 2000000 0.0 (unsafePerformIO (randomList (1,
2000000))))
go :: STArray s Int Tree -> Int -> Double -> [Int] -> ST s Double
go a i acc (x1:x2:xs)
| i < 1 = return acc
| otherwise=do
b <- readArray a x1
writeArray a x2 (setDouble ((getDouble b)+3.0))
c <- readArray a i
go a (i-1) (acc+ (getDouble c)) xs
-- What I really need is a random index in Haskell.
getDouble (L r)= r
getDouble _ = 0.0
setDouble r= L r
randomList r =
do
g <- getStdGen
return $ randomRs r g
-- ghc -O2 --make bingo.hs -fvia-C -optc-O3 -optc-msse3 -o bingo.exe
-- bingo.exe +RTS -sstderr -K100m -H100
}}}
{{{
module boxed;
import StdEnv, MersenneTwister, StdTime;
::Op = AND | OR | NOT;
::Tree= L Real | T Op [Tree];
fn i a acc xs | i<1 = acc;
fn i a acc [x1:x2:xs]
# (i1, i2)= (ri x1, ri x2);
# (b, a)= a![i1];
# a= {a&[i2]= setDouble ((getDouble b)+3.0)};
# (c, a)= a![i];
= fn (i-1) a ((getDouble c)+acc) xs;
ri x= (abs x) rem 2000000;
getDouble (L r)= r;
getDouble _ = 0.0;
setDouble r= L r;
Start w
# (ct,w)= getCurrentTime w;
seed= 1+ct.seconds;
xs= genRandInt seed;
= fn (2000000-1) vt 0.0 xs;
where{
vt:: *{Tree};
vt = createArray 2000000 (L 137.0);}
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3586#comment:14>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs