[Haskell-cafe] about Haskell code written to be "too smart"

Bas van Dijk v.dijk.bas at gmail.com
Tue Mar 24 17:24:07 EDT 2009


2009/3/24 Peter Verswyvelen <bugfact at gmail.com>:
> But aren't these two definitions different algoritms? At first sight I think
> the second one is more efficient than the first one.

Some performance numbers:

----------------------------------------------------------------------

module Main where

import System.Environment (getArgs)
import Control.Monad.State (State(..), evalState)

takeList1, takeList2, takeList3 :: [Int] -> [a] -> [[a]]

takeList1 [] _         =  []
takeList1 _ []         =  []
takeList1 (n : ns) xs  =  head : takeList1 ns tail
    where (head, tail) = splitAt n xs

takeList2 ns xs = zipWith take ns . init . scanl (flip drop) xs $ ns

takeList3 = evalState . mapM (State . splitAt)

test :: Int -> [[Int]]
test n = takeList1 (take n [1..]) [1..]

main :: IO ()
main = print . sum . map sum . test . read . head =<< getArgs

----------------------------------------------------------------------

compile with: ghc --make TakeList.hs -o takeList1 -O2

$ time ./takeList1 5000
739490938

real	0m6.229s
user	0m5.787s
sys	0m0.342s

$ time ./takeList2 5000
739490938

real	0m5.089s
user	0m4.455s
sys	0m0.348s

$ time ./takeList3 5000
739490938

real	0m6.224s
user	0m5.750s
sys	0m0.347s

----------------------------------------------------------------------

regards

Bas


More information about the Haskell-Cafe mailing list