<p dir="ltr">Maybe it is due to using lists and ++? Thats a well know inefficiency.</p>
<div class="gmail_quote">On Nov 19, 2015 9:06 PM, "martin" <<a href="mailto:martin.drautzburg@web.de">martin.drautzburg@web.de</a>> wrote:<br type="attribution"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">I just tried both strict pairs and seq, and it didn't change anything. Also, wouldn't then THUNKS consume a lot of<br>
memory in my heap profile? I forgot to mention that this is not the case. Max heap is around 35k and the top-consumer<br>
is ARR_WORDS. THUNK is below 1k.<br>
<br>
I am going though 10,000,000 iterations and if anything would pile up, it would consume at least one byte per iteration,<br>
wouldn't it? But I can't see 10 MBytes anywhere. It looks as if the time is really spent on *computing* something.<br>
<br>
Am 11/19/2015 um 07:15 PM schrieb Roman Cheplyaka:<br>
> My guess is that you have accumulating thunks inside your (Int,a) tuple.<br>
> Be sure to force them (by using a strict pair type, bang patterns, or<br>
> however else).<br>
><br>
> On 11/19/2015 07:18 PM, martin wrote:<br>
>> Hello all,<br>
>><br>
>> I wrote a Logger which, under certain conditions, prepends log-entries to a log and a Monoid instance of it. But as soon<br>
>> as I mappend two Loggers my performance drops by 50%. This even happens when I mappend  mempty as shown below in --<2--.<br>
>> I understand that the system has to do *something*, but it seems to cost a bit much. Without the strictness annotation<br>
>> in --<1-- the performance degradation is even more dramatic (orders of magnitude).<br>
>><br>
>> The profile tells me that more that 50% of the time is spent in mappend.<br>
>><br>
>> COST CENTRE  MODULE    %time %alloc<br>
>><br>
>> mappend.\    Logger     50.6   35.8<br>
>> logCount'.f  Logger     18.7   40.3<br>
>> logCount'    Logger      5.4    0.0<br>
>><br>
>> Why is that so, and can I do anything about it?  I am willing to change the overall design if required.<br>
>><br>
>><br>
>> This is the code<br>
>><br>
>> -- | A writer does the formatting<br>
>> newtype Wtr a log = Wtr {runWtr :: a -> log}<br>
>><br>
>> -- | A looger is a writer plus an internal state<br>
>> data Logger a log = Lgr {runLogger :: a -> log -> (log, Logger a log)}<br>
>><br>
>> instance Monoid (Logger a log) where<br>
>>         mempty = Lgr (\_ l -> (l,mempty))<br>
>>         mappend lgr1 lgr2 = Lgr $ \a l -> let !(log1',!lgr1') = runLogger lgr1 a l      --<1--<br>
>>                                               !(log2',!lgr2') = runLogger lgr2 a log1'  --<1--<br>
>>                                           in (log2', mappend lgr1' lgr2')<br>
>><br>
>><br>
>> and this is how I test it<br>
>><br>
>> -- | Count calls __s__ and write log when s has reached nxt and then every dn calls<br>
>> logCount' :: Monoid log => Int -> Int -> Int ->  Wtr (Int,a) log -> Logger a log<br>
>> logCount' dn nxt s wtr = Lgr f<br>
>>         where<br>
>>             f a l = if s == nxt<br>
>>                        then (runWtr wtr (s,a)  <> l, logCount'  dn (nxt+dn) (s+1) wtr)<br>
>>                        else (l,                      logCount'  dn nxt      (s+1) wtr)<br>
>><br>
>><br>
>> -- | Count calls and write log every dn calls<br>
>> logCount dn = logCount' dn dn 0<br>
>><br>
>><br>
>> -- testLogger :: Logger Int Int [String] -> [String]<br>
>> testLogger lgr xs = fst $ foldl' f ([],lgr) xs<br>
>>         where<br>
>>             f (log', lgr') x = runLogger lgr' x log'<br>
>><br>
>> ex_wtr :: Wtr (Int,a) [String]<br>
>> ex_wtr = Wtr $ \(x,_) -> ["Counted to " ++ (show x)]<br>
>><br>
>> ex_wtr2 :: Wtr Int [String]<br>
>> ex_wtr2 = Wtr $ \x -> ["Counted to " ++ (show x)]<br>
>><br>
>> ex_inputs :: [Int]<br>
>> ex_inputs = [1..10000000]<br>
>><br>
>> ex_logger = mempty <> logCount 300000 ex_wtr <> mempty                 --<2--<br>
>> -- ex_logger = logCount 300000 ex_wtr<br>
>><br>
>><br>
>> ex_main = do<br>
>>     timeIt $ putStrLn $ ppShow $ testLogger ex_logger ex_inputs<br>
>><br>
>> main = ex_main<br>
>> _______________________________________________<br>
>> Haskell-Cafe mailing list<br>
>> <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
>> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
>><br>
><br>
><br>
><br>
><br>
> _______________________________________________<br>
> Haskell-Cafe mailing list<br>
> <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
><br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div>