Send Beginners mailing list submissions to beginners@haskell.org To subscribe or unsubscribe via the World Wide Web, visit http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners or, via email, send a message with subject or body 'help' to beginners-requ...@haskell.org
You can reach the person managing the list at beginners-ow...@haskell.org When replying, please edit your Subject line so it is more specific than "Re: Contents of Beginners digest..." Today's Topics: 1. How to hunt this space-leak (martin) 2. State Monad in constant space? (martin) 3. Re: How to hunt this space-leak (Romain G?rard) ---------------------------------------------------------------------- Message: 1 Date: Sun, 12 Jun 2016 15:38:02 +0200 From: martin <martin.drautzb...@web.de> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: [Haskell-beginners] How to hunt this space-leak Message-ID: <575d65ba.6030...@web.de> Content-Type: text/plain; charset=utf-8 Hello all, I hope I am not asking for too much, as to explain my problem, you need to read my code, which may not be a pleasure. I am trying to write a "Logger", which formats and accumulates log-entries in a monoid. From there I went to writing an "accumulating" logger, i.e. one which can accumulate (sum/avg) over entries made with a certain timespan. My problen is memory consumption. In the test below I stress the logger with 1 million values, but in the end result, there are only 10 entries left, because it accumulates over 100,000. Memory goes up to apx 100MB. When I comment out the line, which logs the accumulated value (see -- > below), memory stays below 10MB. I dont understand why this is so. After all, the difference is only whether or not those 10 entries are logged or not. Can someone explain this? {-# LANGUAGE BangPatterns#-} import Data.Monoid import Control.Monad.State.Strict import System.TimeIt import Text.Show.Pretty import Debug.Trace ------------------------------------------------------------ -- Simple Time Stuff ------------------------------------------------------------ type Instant = Double type Interval = Double type Timed a = (Instant, a) instant = fst ------------------------------------------------------------ -- Logger based on State monad ------------------------------------------------------------ data SLogger a l = SLgr {runSLogger :: a ->State l (SLogger a l)} type SLogFormatter a l = a -> l accLogger :: (Monoid c, Show a) => (Instant, Interval, [Timed b]) -> SLogFormatter (Timed a) [Timed b] -> SLogFormatter [Timed b] [Timed c] -> SLogger (Timed a) [Timed c] accLogger (tx, dt, tas) fmt1 fmt2 = SLgr $ \(!ta) -> let x = fmt1 ta !tas' = x <> tas in if instant ta < tx then do -- keep accumulating return $ accLogger (tx, dt, tas') fmt1 fmt2 else do -- compute new log and reset accumulator !l0 <- get -- > put $ fmt2 tas' <> l0 return $ accLogger ((tx+dt), dt, []) fmt1 fmt2 accFmt1 ta = [ta] accFmt2 tas = [(fst $ head tas, "hello from accFormatter")] -- apply logger to a list of as stest lgr [] = return lgr stest lgr (a:as) = do lgr' <- (runSLogger lgr) a stest lgr' as main2 = do let as = zip [1.0 .. 1000000.0] [1..1000000] :: [(Instant, Int)] log = execState (stest (accLogger (100000.0,100000.0,[]) accFmt1 accFmt2 ) as) [(0,"init")] timeIt $ putStrLn $ ppShow log putStrLn "done" main = main2 ------------------------------ Message: 2 Date: Sun, 12 Jun 2016 23:11:05 +0200 From: martin <martin.drautzb...@web.de> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: [Haskell-beginners] State Monad in constant space? Message-ID: <575dcfe9.7070...@web.de> Content-Type: text/plain; charset=utf-8 Hello all, the State Monad wraps around a computation s -> (s,a). Inside a do block I am actually assembling such a computation. Now when I do this many times, i.e. in a recursice call, I am builing a huge expression m a >>= (\a -> mb) >>= (\b -> mc) ... The result of this expression is a function s -> (s,a). But I cannot see how the space for this expression can be reclaimed, and how it could ever run in constant space. Once I call runState and I provide an initial s, I have some hope, but before? How is this supposed to work? How do I avoid allocating space for this huge expression? ------------------------------ Message: 3 Date: Mon, 13 Jun 2016 13:13:39 +0200 From: Romain G?rard <hask...@erebe.eu> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] How to hunt this space-leak Message-ID: <00c0c074424926dde09858a61f163...@erebe.eu> Content-Type: text/plain; charset=UTF-8; format=flowed Hello, I have used the technique described below[1] with great success. To be fair, debugging space leak in haskell is kinda hard, even knowing that you have one is a big step forward. Maybe it is possible to create a program like valgrind for haskell, but I lack the knowledge to tell if it's possible or not. [1] http://neilmitchell.blogspot.fr/2015/09/detecting-space-leaks.html Regards Le 2016-06-12 15:38, martin a ?crit?: > Hello all, > > I hope I am not asking for too much, as to explain my problem, you > need to read my code, which may not be a pleasure. > > I am trying to write a "Logger", which formats and accumulates > log-entries in a monoid. From there I went to writing an > "accumulating" logger, i.e. one which can accumulate (sum/avg) over > entries made with a certain timespan. > > My problen is memory consumption. In the test below I stress the > logger with 1 million values, but in the end result, > there are only 10 entries left, because it accumulates over 100,000. > Memory goes up to apx 100MB. > > When I comment out the line, which logs the accumulated value (see -- > > below), memory stays below 10MB. I dont > understand why this is so. After all, the difference is only whether > or not those 10 entries are logged or not. > > Can someone explain this? > > > > {-# LANGUAGE BangPatterns#-} > > > import Data.Monoid > import Control.Monad.State.Strict > import System.TimeIt > import Text.Show.Pretty > import Debug.Trace > > > ------------------------------------------------------------ > -- Simple Time Stuff > ------------------------------------------------------------ > type Instant = Double > type Interval = Double > type Timed a = (Instant, a) > instant = fst > > ------------------------------------------------------------ > -- Logger based on State monad > ------------------------------------------------------------ > > data SLogger a l = SLgr {runSLogger :: a ->State l (SLogger a l)} > type SLogFormatter a l = a -> l > > > accLogger :: (Monoid c, Show a) => > (Instant, Interval, [Timed b]) -> > SLogFormatter (Timed a) [Timed b] -> SLogFormatter [Timed > b] [Timed c] -> SLogger (Timed a) [Timed c] > > > accLogger (tx, dt, tas) fmt1 fmt2 = SLgr $ \(!ta) -> > let x = fmt1 ta > !tas' = x <> tas > in > if instant ta < tx > then do > -- keep accumulating > return $ accLogger (tx, > dt, tas') fmt1 fmt2 > else do > -- compute new log and > reset accumulator > !l0 <- get > -- > put $ fmt2 tas' <> l0 > return $ accLogger > ((tx+dt), dt, []) fmt1 fmt2 > > > > accFmt1 ta = [ta] > accFmt2 tas = [(fst $ head tas, "hello from accFormatter")] > > -- apply logger to a list of as > stest lgr [] = return lgr > stest lgr (a:as) = do > lgr' <- (runSLogger lgr) a > stest lgr' as > > > main2 = do > let as = zip [1.0 .. 1000000.0] [1..1000000] :: [(Instant, Int)] > log = execState (stest (accLogger (100000.0,100000.0,[]) > accFmt1 accFmt2 ) as) [(0,"init")] > timeIt $ putStrLn $ ppShow log > putStrLn "done" > > > > main = main2 > > > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ Subject: Digest Footer _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ End of Beginners Digest, Vol 96, Issue 10 *****************************************