[Haskell-cafe] how to optmize this code?

Gilberto Garcia giba.dmb at gmail.com
Mon Apr 11 14:41:06 CEST 2011


Hi Guys,

Thanks all for the suggestions, I have certainly improved my knowledge.
I made a blog post to show all the possible solution a problem can
have. you can check it out at katacoder.blogspot.com

Giba

On Sun, Apr 10, 2011 at 3:35 AM, Johan Tibell <johan.tibell at gmail.com> wrote:
> Hi Gilberto,
>
> On Wed, Mar 30, 2011 at 4:39 PM, Gilberto Garcia <giba.dmb at gmail.com> wrote:
>> fkSum :: Int -> [Int] -> Int
>> fkSum a [] = 0
>> fkSum a (b) = foldl (+) 0 (filter (\x -> isMultiple x b) [1..a])
>>
>> isMultiple :: Int -> [Int] -> Bool
>> isMultiple a [] = False
>> isMultiple a (x:xs) = if (mod a x == 0) then True else isMultiple a xs
>
> You can make both these functions a little bit more efficient by
> making them strict in the first argument, like so:
>
> {-# LANGUAGE BangPatterns #-}
>
> fkSum :: Int -> [Int] -> Int
> fkSum !a [] = 0
> fkSum a (b) = foldl (+) 0 (filter (\x -> isMultiple x b) [1..a])
>
> isMultiple :: Int -> [Int] -> Bool
> isMultiple !a [] = False
> isMultiple a (x:xs) = if (mod a x == 0) then True else isMultiple a xs
>
> This change ensures that the first argument is always evaluated.
> Before `fkSum undefined []` would return 0, now it results in an
> error. The upside is that when a function is strict in an argument,
> GHC can use a more efficient calling convention for the function. In
> this case it means that instead of passing the first argument as a
> pointer to a machine integer, it can pass the machine integer directly
> (in a register).
>
> This optimization is particularly worthwhile for accumulator parameters.
>
> Johan
>



More information about the Haskell-Cafe mailing list