[Haskell-cafe] Shootout favoring imperative code

Chris Kuklewicz haskell at list.mightyreason.com
Thu Jan 5 16:13:47 EST 2006


This uses getLine instead of getContents and is 3.8 times slower.


{-# OPTIONS -fglasgow-exts -O2 #-}
--
-- The Computer Language Shootout
-- http://shootout.alioth.debian.org/
--
-- compile with : ghc -O2 -o SumF SumF.hs
-- To get better performance set default heap size to 10MB
-- i.e. invoke as : ./SumF +RTS -H10M <input_file.txt
-- contributed by Greg Buchholz
-- modified by Mirko Rahn
-- modified by Chris Kuklewicz, 5 Jan 2006
--
import Data.Char(ord)
import GHC.Base

{-# INLINE d2i #-}
d2i :: Char -> Int#
d2i c = let (I# x) = ord c
            (I# z) = ord '0'
        in x -# z

main :: IO ()
main = do
  let next rt = do line <- catch getLine (\_ -> return [])
                   if (null line) then return (I# rt)
                                  else next (rt +# aLine line)
      aLine ('-':rest) = nLine rest 0#
          where nLine [] soFar = (-1#) *# soFar
                nLine ( x  :rest) soFar = nLine rest (d2i x +# (10# *#
soFar))
      aLine (x:rest) = pLine rest (d2i x)
          where pLine [] soFar = soFar
                pLine ( x  :rest) soFar = pLine rest (d2i x +# (10# *#
soFar))
  total <- next 0#
  print total


Sebastian Sylvan wrote:
> On 1/5/06, Chris Kuklewicz <haskell at list.mightyreason.com> wrote:
> 
>>I did manage to tweak SumFile to use unboxed Int# and go 10% faster.
>>
>>http://haskell.org/hawiki/SumFile
> 
> 
> Interestingly, it's actually faster to do it this way than to call the
> C functions fgets and atoi...
> 
> However, I'm not sure it's "legal" since it's not using built-in
> line-based IO functions (which the spec states, for no apparent reason
> other than to favor languages whose IO convenience functions are
> low-level :-))
> 
> /S
> 
> --
> Sebastian Sylvan
> +46(0)736-818655
> UIN: 44640862
> 



More information about the Haskell-Cafe mailing list