[Haskell-beginners] A better way?
Daniel Fischer
daniel.is.fischer at web.de
Sat Feb 21 20:03:30 EST 2009
Am Sonntag, 22. Februar 2009 01:32 schrieb Keith Sheppard:
> ghci still is not happy if we have many rows...
>
> Prelude> :load Table.IO
> [1 of 1] Compiling Table.IO ( Table/IO.hs, interpreted )
> Ok, modules loaded: Table.IO.
> *Table.IO> let maxTableColumnWidths = foldr ((evalList .) . zipWithD
> max) [] . map (map length)
> *Table.IO> let maxTCWs = evalList . foldr (zipWithD max) [] . map (map
> length) *Table.IO> maxTableColumnWidths (replicate 1000000 ["hello",
> "world"]) *** Exception: stack overflow
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)
> *Table.IO> maxTCWs (replicate 1000000 ["hello", "world"])
> *** Exception: stack overflow
That doesn't surprise me in the least. One has to force the list in each step.
>
> I hadn't thought of using ByteStrings since I don't know what they are
ByteStrings are basically byte arrays. Thus if you're dealing exclusively with
characters in the range 0-255, you need only one byte per character, while
with Strings, you need four bytes for each character itself, plus several
machine words for pointers (list cell to Char, list cell to next), I don't
remember, but I think it amounts to 12 or 20 bytes per character.
>
> :-). I'll have to look into it, but I'm assuming that ByteStrings will
>
> give some constant time/space improvement?
Can be several orders of magnitude faster, and as said above, they use far
less memory (but they're useful only for long enough strings, having a
multitude of short ByteStrings floating around doesn't do any good).
> I think it won't help with
> my first problem though since what's happening is that the lazy
> function calls are piling up too deep (at least thats what I think is
> happening).
Yes, that's basically what *** Exception: stack overflow means :)
>
> Thank you
> Keith
>
Cheers,
Daniel
More information about the Beginners
mailing list