[Haskell-cafe] Why doesn't this consume all the computer's memory?
Tyson Whitehead
twhitehead at gmail.com
Thu Nov 8 16:04:34 UTC 2018
On Thu, 8 Nov 2018 at 01:09, Tyson Whitehead <twhitehead at gmail.com> wrote:
> Sorry for all the noise. I believe I finally tracked down the eat all the memory/don't eat all the memory trigger. It is the view pattern.
There was a request to post both codes as it seems a bit unexpected
that a view pattern would make that difference.
Here they are. I compiled both with `ghc file.hs` using the standard
GHC 8.4.3 from NixOS 18.09.
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