Hi, after having adapted "binaries-tree" from http://shootout.alioth.debian.org/u32q/benchmark.php?test=binarytrees&lang=ghc&box=1 to remove the dependency on Text.Printf (program below), I get the following results. 1. reference run. $ghc --make -O2 -fglasgow-exts -fasm prog.hs -o prog.ghc $./prog.ghc 1 "stretch tree" of depth 7 check: -1 "128 trees" of depth 4 check: -128 "32 trees" of depth 6 check: -32 "long lived tree" of depth 6 check: -1 2. jhc run. $jhc -o prog of depth 77 check: -1 of depth 44 check: -128 of depth 66 check: -32 of depth 66 check: -1 $ ./prog.jhc 18 of depth 1919 check: -1 segmentation fault Maybe is it time to set up a bug tracker :) Sylvain --snip-- import System import Data.Bits -- -- an artificially strict tree. -- -- normally you would ensure the branches are lazy, but this benchmark -- requires strict allocation. -- data Tree = Nil | Node !Int !Tree !Tree minN = 4 io s n t = putStrLn (show s++" of depth "++(show n)++" check: "++(show t)) main = do n <- getArgs >>= readIO . head let maxN = max (minN + 2) n stretchN = maxN + 1 -- stretch memory tree let c = check (make 0 stretchN) io "stretch tree" stretchN c -- allocate a long lived tree let long = make 0 maxN -- allocate, walk, and deallocate many bottom-up binary trees let vs = depth minN maxN mapM_ (\((m,d,i)) -> io (show m ++ " trees") d i) vs -- confirm the the long-lived binary tree still exists io "long lived tree" maxN (check long) -- generate many trees depth :: Int -> Int -> [(Int,Int,Int)] depth d m | d <= m = (2*n,d,sumT d n 0) : depth (d+2) m | otherwise = [] where n = 1 `shiftL` (m - d + minN) -- allocate and check lots of trees sumT :: Int -> Int -> Int -> Int sumT d 0 t = t sumT d i t = sumT d (i-1) (t + a + b) where a = check (make i d) b = check (make (-i) d) -- traverse the tree, counting up the nodes check :: Tree -> Int check Nil = 0 check (Node i l r) = i + check l - check r -- build a tree make :: Int -> Int -> Tree make i 0 = Node i Nil Nil make i d = Node i (make (i2-1) d2) (make i2 d2) where i2 = 2*i; d2 = d-1 --snip--
Interesting. I actually use BinaryTrees as a test because it has the known bug that it segfaults at 17 or above as the argument. It actually tickles a memory leak in the generated code, and is quite reproducable so I have been using it to diagnose said memory leak. However, I somehow never noticed that it wasn't printing out the strings at the beginning of the lines. that seems like a more interesting bug. hmm.... Also, I thought Text.Printf was working in jhc, is it not for you? perhaps I forgot to include it in base in my latest build or accidentally broke it, A regression test that hammered Text.Printf would be useful as it would cover a lot of interesting bits of the class system implementation. If anyone wants to write one that would be great. As far as bug trackers go, anyone have preferences for bugzilla vs trac? I have a bugzilla set up already for other projects so that is quite easy, but I notice a lot of people seem to like trac nowadays but I am less familiar with that. I wish fogbugz were free for open source projects, it is really nice. John -- John Meacham - ⑆repetae.net⑆john⑈
On Fri, Mar 20, 2009 at 5:15 PM, John Meacham
I wish fogbugz were free for open source projects, it is really nice.
You could always ask. They have a free student edition, and apparently
discounted academic pricing.
--
Taral
participants (3)
-
John Meacham -
sylvain -
Taral