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

martin martin.drautzburg at web.de
Sat Nov 14 16:17:41 UTC 2015


Thanks Tom,

with lots of trial and error I believe I finally put the exclamation marks in the right spots, but I still don't understand.

addLgr (lgr1) (lgr2) = Lgr lgr
        where
            lgr tev dom = let (!(log1', lgr1')) = runLogger lgr1  tev dom
                              (!(log2', lgr2')) = runLogger lgr2  tev dom
                              (!log') = log1' <> log2'
                          in (log', addLgr lgr2' lgr1')

I had previously put the marks inside the tuples as in (!log1', !lgr1') but that didn't help. Can someone explain the
difference between (!log1', !lgr1') and !(log1', lgr1'). I thought the former enforces more strictness than the later,
but I must be missing something.

Am 11/14/2015 um 01:43 PM schrieb Tom Ellis:
> On Sat, Nov 14, 2015 at 01:28:58PM +0100, martin wrote:
>> 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.
> 
> Sure, this
> 
>     (log', lgrIn') = runLogger lgrIn tev dom
> 
> allocates a thunk for log' that holds on to tev and dom.  Even if they are
> small, holding onto them for thousands or millions of iterations is going to
> leak a lot of space.
> 
> The only way to avoid this is to force log' sufficiently far that tev and
> dom can be released.
> 
> Tom
> _______________________________________________
> 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