[Haskell-cafe] another laziness blowup (this one unsolved)
Thomas Hartman
tphyahoo at gmail.com
Thu Jul 16 20:10:39 EDT 2009
Is it possible to fix alternate' (the second version), or otherwise
define a fast stepwise alternate that doesn't blow up on long lists?
alternate just breaks up [1,2,3,4,5] into ([1,3,5],[2,4])
Thanks!
{-# LANGUAGE BangPatterns #-}
import Data.List
import Control.Arrow
import Control.Parallel.Strategies
t = (last *** last) $! alternate $ [1..(10^6)]
t' = (last *** last) $! alternate' $ [1..(10^6)]
t'' = (last *** last) $! alternate'' $ [1..(10^6)]
-- finishes reasonably fast, but does a separate computation for the
list and its tail rather than just rip through it
alternate x = (skip1 x,(skip1 $ tail x))
skip1 = skip 1
skip n xs =
let (a,b) = splitAt (n+1) xs
in case a of
[] -> []
x:_ -> x : skip n b
-- this one overflows on million element list, even after fiddling
with strictness on input args. can this be fixed?
alternate' xs =
let f3 :: Int -> (([Int],[Int]),Int) -> (([Int],[Int]),Int)
f3 x ((a,b),n) = -- rnf (x,((a,b),n)) `seq`
let nxtn = n+1
in if n `mod` 2 == 0
then ((x:a,b),nxtn)
else ((a,x:b),nxtn)
in fst . foldr f3 (([],[]),0) $ xs
-- no overflow, goes through the list stepwise, but it's actually
slightly slower than the first alternate because of the reverses
alternate'' xs =
let f3 ((a,b),n) x =
(let nxtn = n+1
in if n `mod` 2 == 0
then ((x:a,b),nxtn)
else ((a,x:b),nxtn) )
in (reverse *** reverse) . fst . foldl' f3 (([],[]),0) $ xs
More information about the Haskell-Cafe
mailing list