[Haskell-cafe] Why doesn't this consume all the computer's memory?
Tom Ellis
tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk
Thu Nov 8 18:13:01 UTC 2018
I must admit I'm stumped! I don't see any significant difference between
those two programs.
On Thu, Nov 08, 2018 at 11:04:34AM -0500, Tyson Whitehead wrote:
> Constant memory code (RES 6MB):
>
> {-# LANGUAGE ViewPatterns #-}
>
> module Main (main) where
>
> import Data.Either
>
> (length -> lx,length -> ly) = partitionEithers (repeat $ Left ())
>
> main = do
> print lx
> print ly
>
> Unbounded memory:
>
> module Main (main) where
>
> import Data.Either
>
> (xs, ys) = partitionEithers (repeat $ Left ())
>
> main = do
> print $ length xs
> print $ length ys
>
> Cheers! -Tyson
>
> PS: The constant-memory view-pattern version seems to compile down to
>
> lxly = case partitionEithers (repeat $ Left ()) of
> (xs,ys) -> (length xs,length ys)
>
> main = do
> print (case lxly of (lx,_) -> lx)
> print (case lxly of (_,ly) -> ly)
>
> while the unbounded-memory non-view-pattern one compiles down to
>
> xsys = partitionEithers (repeat $ Left ())
> xs = case xsys of (xs,_) -> xs
> ys = case xsys of (_,ys) -> ys
>
> main = do
> print (length xs)
> print (length ys)
More information about the Haskell-Cafe
mailing list