[Haskell-beginners] Re: A better way?
Heinrich Apfelmus
apfelmus at quantentunnel.de
Sun Feb 22 09:30:55 EST 2009
Daniel Fischer wrote:
>
> Yes, foldr was the wrong choice. make it foldl' (don't forget the prime at the
> end) and it works for large tables. If the rows are short, it actually is
> faster (here) than your version, but if the rows are long , e.g.
>
> maxTableColumnWidths (replicate 2000 (replicate 1000 "what?"))
>
> your version is faster than
>
> import Data.List (foldl')
>
> seqList [] = False
> seqList (head:tail)
> | head `seq` False = undefined
> | otherwise = seqList tail
>
> evalList xs
> | seqList xs = undefined
> | otherwise = xs
>
> zipWithD :: (a -> a -> a) -> [a] -> [a] -> [a]
> zipWithD f (x:xt) (y:yt) = f x y:zipWithD f xt yt
> zipWithD _ [] ys = ys
> zipWithD _ xs [] = xs
>
> maxTableColumnWidths =
> foldl' ((evalList .) . zipWithD max) [] . map (map length)
Nice! I'd use bang patterns in favor of the now outdated
| x `seq` False = undefined
pattern though.
Actually, I'd use
import Control.Parallel.Strategies
maxWidths = foldl' (\xs ys -> zipWithD max xs ys `using` rnf) []
. map (map length)
The module quite useful for controlling evaluation, even when no
parallelism is involved.
Regards,
apfelmus
--
http://apfelmus.nfshost.com
More information about the Beginners
mailing list