Shootout/Binary trees

From HaskellWiki
< Shootout
Revision as of 02:53, 4 October 2006 by DonStewart (talk | contribs) (move GSL sub page)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

Proposals

Port the Clean entry.

Current

Shortest entry in any language, and almost twice as fast as old entry on my box.

{-# OPTIONS_GHC -fglasgow-exts -O2 -optc-O3 -funbox-strict-fields #-}
-- The Great Computer Language Shootout
-- http://shootout.alioth.debian.org/
-- Simon Marlow
-- Shortened by Don Stewart

import System; import Text.Printf; import Monad

data Tree = Nil | Node !Int Tree Tree

min' = 4 :: Int

main = do max' <- getArgs >>= return . max (min'+2) . read . head
          printf "stretch tree of depth %d\t check: %d\n" (max'+1) (itemCheck $ make 0 (max'+1))
          depthLoop min' max'
          printf "long lived tree of depth %d\t check: %d\n" max' (itemCheck $ make 0 max')

depthLoop d m = when (d <= m) $ do
    printf "%d\t trees of depth %d\t check: %d\n" (2*n) d (sumLoop n d 0)
    depthLoop (d+2) m 
    where n = 2^(m - d + min')

sumLoop 0 d acc = acc
sumLoop k d acc = c `seq` sumLoop (k-1) d (acc + c + c')
    where (c,c')  = (itemCheck (make k d), itemCheck (make (-1*k) d))

make i (0::Int) = i `seq` Nil
make i  d       = Node i (make ((2*i)-1) (d-1)) (make (2*i) (d-1))

itemCheck Nil = 0
itemCheck (Node x l r) = x + itemCheck l - itemCheck r

Old Entry

{-# OPTIONS -O3 -optc-O3 #-}
-- The Great Computer Language Shootout
-- http://shootout.alioth.debian.org/
-- contributed by Einar Karttunen

import System

data Tree = Node  Int Tree Tree | Nil

main = do [n] <- getArgs
          let max' = max (min'+2) (read n)
          showItemCheck (max'+1) (make 0 (max'+1)) "stretch tree of depth "
          let longlived = make 0 max'
          depthLoop min' max'
          showItemCheck max' longlived "long lived tree of depth "

min' :: Int
min' = 4

showItemCheck d a s = putStrLn (s++show d++"\t check: "++show (itemCheck a))

showCheck i d check = putStrLn (show (2*i)++"\t trees of depth "++show d++"\t check: "++show check)


depthLoop d m | d > m = return ()
depthLoop d m         = showCheck n d (sumLoop n d 0) >> depthLoop (d+2) m
              where n = 2^(m - d + min')



sumLoop :: Int -> Int -> Int -> Int
sumLoop 0 d acc = acc
sumLoop k d acc = c `seq` sumLoop (k-1) d (acc + c + c')
    where c  = itemCheck (make k d)
          c' = itemCheck (make (-1*k) d)

make :: Int -> Int -> Tree
make i 0 = Nil
make i d = Node i (make ((2*i)-1) (d-1)) (make (2*i) (d-1))

itemCheck Nil = 0
itemCheck (Node x l r) = x + itemCheck l - itemCheck r