[Haskell-cafe] Daunting heap profile when using (<>)

martin martin.drautzburg at web.de
Sat Nov 14 12:28:58 UTC 2015


I profiled the program and the profile does not say anything about THUNKs. Instead the main culprit seems to be

(352)cor.cnd/cor/ex_lgr.lo...	2837612

This probably points to this function:

newtype Condition a  = Cnd {checkCnd :: a ->  (Bool, Condition a)}

-- | Create a 'Condition' from two conditions which holds when one of
-- them holds.
cor :: Condition a -> Condition a -> Condition a
cor c1 c2 = Cnd cnd
        where
            cnd a = let (b1', c1') = checkCnd c1 a
                        (b2', c2') = checkCnd c2 a
                    in if b1' || b2'
                       then (True,  cor c1' c2')
                       else (False, cor c1 c2)


logWhen :: Monoid log => Condition (Timed evt,dom) -> Logger evt dom log -> Logger evt dom log
logWhen cnd lgrIn = Lgr lgr'
        where
            lgr' tev dom =
                    case checkCnd cnd (tev, dom) of
                        (True, cnd') -> let (log', lgrIn') = runLogger lgrIn tev dom
                                         in (log', logWhen cnd' lgrIn')
                        (False,cnd')   -> (mempty, logWhen cnd' lgrIn)

Am I holding on to some data where I shouldn't? I cannot see it.


Am 11/14/2015 um 11:10 AM schrieb martin:
> Hello all,
> 
> I have a Logger which produces log entries and a new version of itself
> 
> newtype Logger evt dom log = Lgr {runLogger :: Timed evt -> dom -> (log, Logger evt dom log)}
> 
> Loggers are used in a function like this
> 
> runSim :: (Ord evt, Monoid log) => SimBehaviour evt dom log -> SimState evt dom log -> SimState evt dom log
> runSim (!lgr, !hdr, xtp) (!log,!dom,!evq)  =
>         case step of
>             Nothing -> (log, dom, evq) -- end of simulation
>             Just (newEvq, newDom, newHdr, newLgr, newLog) -> runSim (newLgr,newHdr,xtp) (newLog,newDom,newEvq)
>         where
>             -- check for end conditions or run handler
>             step = do
>                 (evt, evts) <- H.view evq -- no more Events -> Nothing
>                 if xtp (evt,dom)  then Nothing
>                 else
>                         let (evq', dom', hdr') = runHandler hdr evt dom
>                             (log',lgr')        = runLogger lgr evt dom'        -- <--
>                         -- append new event and new log entries
>                         in return (evq'<>evts, dom', hdr', lgr', log'<>log)    -- <--
> 
> 
> 
> I then wrote a function to combine two Loggers
> 
> addLgr (lgr1) (lgr2) = Lgr lgr
>         where
>             lgr tev dom = let (log1', lgr1') = runLogger lgr1  tev dom
>                               (log2', lgr2') = runLogger lgr2  tev dom
>                               (!log') = log2'  <> log1'                       -- x --
> --                          in (log2', addLgr lgr1' lgr2')
>                           in (log', addLgr lgr1' lgr2')
> 
> 
> When called a million times, this produces a heap profile which climbs steadily (with or without the stricness
> annotation in line x). When I omit the (<>) as in the commented line, the heap stays flat. My log is really just a list
> of strings and most of the time the loggers do not produce any output, i.e. they return an empty list.
> 
> Am I on the right track, that this trouble is probably caused by laziness and that forcing strictness is the way to go?
> 
> Could it be that this is because ! does not fully evaluate its argument, but just to WHNF? Or is there a more obvious
> reason, I just fail to see.
> 
> Where to go from here?
> 
> 
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> 



More information about the Haskell-Cafe mailing list