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