Re: [Haskell-cafe] how to optmize this code?

2011-04-11 Thread Gilberto Garcia
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.tib...@gmail.com wrote:
 Hi Gilberto,

 On Wed, Mar 30, 2011 at 4:39 PM, Gilberto Garcia giba@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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-04-10 Thread Johan Tibell
Hi Gilberto,

On Wed, Mar 30, 2011 at 4:39 PM, Gilberto Garcia giba@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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-04-09 Thread Henning Thielemann
Gilberto Garcia schrieb:

 isMultiple :: Int - [Int] - Bool
 isMultiple a [] = False
 isMultiple a (x:xs) = if (mod a x == 0) then True else isMultiple a xs

I think this one can be written in terms of 'List.any'.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-31 Thread Christian Maeder

Am 31.03.2011 05:59, schrieb Felipe Almeida Lessa:

On Wed, Mar 30, 2011 at 2:39 PM, Gilberto Garciagiba@gmail.com  wrote:

fkSum :: Int -  [Int] -  Int
fkSum a [] = 0
fkSum a (b) = foldl (+) 0 (filter (\x -  isMultiple x b) [1..a])


Daniel Fischer and Yves Parès gave you good suggestions about
implementing a different, better algorithm for you problem.  However,
there's one small thing about your current code.  Instead of foldl,
you should use foldl' (use import Data.List), which is strict in the
accumulator.  Most of the time you want foldl' instead of foldl.  You
can learn more about the list folds here [1].


Since we don't have a function sum' in the Prelude (should we have it?) 
I wonder what happens if you just use sum. Will the sum (based on 
sum' so without -DUSE_REPORT_PRELUDE) be strict enough?


#ifdef USE_REPORT_PRELUDE
sum =  foldl (+) 0
product =  foldl (*) 1
#else
sum l   = sum' l 0
  where
sum' [] a = a
sum' (x:xs) a = sum' xs (a+x)
product l   = prod l 1
  where
prod [] a = a
prod (x:xs) a = prod xs (a*x)
#endif

Cheers C.

P.S.

isMultiple a = any ((== 0) . mod a)



HTH,

[1] http://www.haskell.org/haskellwiki/Foldr_Foldl_Foldl%27



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-31 Thread Daniel Fischer
On Thursday 31 March 2011 11:45:00, Christian Maeder wrote:
 Since we don't have a function sum' in the Prelude (should we have it?) 

I think we should.

 I wonder what happens if you just use sum. Will the sum (based on 
 sum' so without -DUSE_REPORT_PRELUDE) be strict enough?

I don't know about other compiler's behaviour, but for GHC, it will be 
strict enough *if compiled with optimisations*, but not without (the 
strictness analyser runs only with optimisations turned on).
- Of course, given a type signature that allows strictness to be inferred.

However, the same holds for 'foldl (+) 0'. In fact, in the presence of a 
suitable type signature, with optimisations turned on, both produce nearly 
identical code (the order of parameters in the recursive loop is changed, 
sometimes parameter order can make a surprisingly large difference, but 
whether it's better to have the list or the accumulator first depends).

The difference is that the explicit recursion produces the better code even 
with optimisations turned off, except that the overload of (+) to use is 
not inlined, so the accumulator still builds a thunk, while with 
optimisations you get the specialised strict additions (+# resp. 
plusInteger, ...) so you have the strictness you need.

 
 #ifdef USE_REPORT_PRELUDE
 sum =  foldl (+) 0
 product =  foldl (*) 1
 #else
 sum l   = sum' l 0
where
  sum' [] a = a
  sum' (x:xs) a = sum' xs (a+x)
 product l   = prod l 1
where
  prod [] a = a
  prod (x:xs) a = prod xs (a*x)
 #endif
 
 Cheers C.
 
 P.S.
 
 isMultiple a = any ((== 0) . mod a)

For Int (and most other types),

isMultiples a = any ((== 0) . rem a)

will be faster (mod is implemented using rem).
However, for checks other than comparisons with 0, one needs to be aware of 
the differences of rem and mod, the latter does what one would expect, rem 
can badly surprise the unaware.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-31 Thread Yves Parès
Just to be sure, because I am not quite familiar with the dark hairy
internals of GHC:

 Of course, given a type signature that allows strictness to be inferred.

You mean a signature with no type variables and types that are know to GHC
as being strict?
(Like Int - Int - Int instead of (Num a) = a - a - a)

 The difference is that the explicit recursion produces the better code
even
 with optimisations turned off, except that the overload of (+) to use is
 not inlined, so the accumulator still builds a thunk, while with
 optimisations you get the specialised strict additions (+# resp.
 plusInteger, ...) so you have the strictness you need.

(+#) is then the GHC's strict equivalent of (+)?
But if you make an overlay to (+), like, say:

(?) :: (Num a) = a - a - a
a ? b = a + b

Then (?) will be lazy, won't it?
Then optimizations will not occur, a ? b will remain a thunk and not be
replaced by a +# b and be strictly evaluated?

If so, then it means that you can always turn a strict function into a non
strict one, am I right?


2011/3/31 Daniel Fischer daniel.is.fisc...@googlemail.com

 On Thursday 31 March 2011 11:45:00, Christian Maeder wrote:
  Since we don't have a function sum' in the Prelude (should we have it?)

 I think we should.

  I wonder what happens if you just use sum. Will the sum (based on
  sum' so without -DUSE_REPORT_PRELUDE) be strict enough?

 I don't know about other compiler's behaviour, but for GHC, it will be
 strict enough *if compiled with optimisations*, but not without (the
 strictness analyser runs only with optimisations turned on).
 - Of course, given a type signature that allows strictness to be inferred.

 However, the same holds for 'foldl (+) 0'. In fact, in the presence of a
 suitable type signature, with optimisations turned on, both produce nearly
 identical code (the order of parameters in the recursive loop is changed,
 sometimes parameter order can make a surprisingly large difference, but
 whether it's better to have the list or the accumulator first depends).

 The difference is that the explicit recursion produces the better code even
 with optimisations turned off, except that the overload of (+) to use is
 not inlined, so the accumulator still builds a thunk, while with
 optimisations you get the specialised strict additions (+# resp.
 plusInteger, ...) so you have the strictness you need.

 
  #ifdef USE_REPORT_PRELUDE
  sum =  foldl (+) 0
  product =  foldl (*) 1
  #else
  sum l   = sum' l 0
 where
   sum' [] a = a
   sum' (x:xs) a = sum' xs (a+x)
  product l   = prod l 1
 where
   prod [] a = a
   prod (x:xs) a = prod xs (a*x)
  #endif
 
  Cheers C.
 
  P.S.
 
  isMultiple a = any ((== 0) . mod a)

 For Int (and most other types),

 isMultiples a = any ((== 0) . rem a)

 will be faster (mod is implemented using rem).
 However, for checks other than comparisons with 0, one needs to be aware of
 the differences of rem and mod, the latter does what one would expect, rem
 can badly surprise the unaware.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-31 Thread Daniel Fischer
On Thursday 31 March 2011 14:27:59, Yves Parès wrote:
 Just to be sure, because I am not quite familiar with the dark hairy
 
 internals of GHC:
  Of course, given a type signature that allows strictness to be
  inferred.
 
 You mean a signature with no type variables and types that are know to
 GHC as being strict?
 (Like Int - Int - Int instead of (Num a) = a - a - a)
 

Yes. For a type class polymorphic function like (+), it is of course 
impossible to infer strictness, since there can be strict as well as lazy 
instances.
For monomorphic types, it may be possible to infer strictness (the 
implementation can be too complicated for the strictness analyser to 
discover that yes, this function is strict, you may as well evaluate 
things immediately).

One important thing for (in particular type class) polymorphic functions is 
to generate specialised versions for frequently used types to let GHC take 
advantage of their properties, so it's generally a good idea to

{-# SPECIALISE foo :: Int - Int - Int,
  Integer - Integer - Integer,
  Double - Double - Double
  #-}

if strictness helps in foo (and compile the defining module as well as the 
using modules with optimisations) [to reduce code bloat, specialise only 
for the types you really use/expect to be used much].

For things like arithmetic operations on Int or Integer, strictness is 
known, so you get immediate evaluation (with optimisations) as soon as the 
analyser sees if the result of some function is ever needed, it needs to 
evaluate this arithmetic expression.

In foldl (+) 0 :: [Int] - Int, that means, if the function is entered at 
all, you get a nice strict loop adding things on the fly and a wrapper 
providing the outermost laziness, guarding the entrance.

  The difference is that the explicit recursion produces the better code
 
 even
 
  with optimisations turned off, except that the overload of (+) to use
  is not inlined, so the accumulator still builds a thunk, while with
  optimisations you get the specialised strict additions (+# resp.
  plusInteger, ...) so you have the strictness you need.
 
 (+#) is then the GHC's strict equivalent of (+)?

(+#) is addition of unboxed Ints.

In GHC, we have

data Int = I# Int#

and Int# is a raw machine integer (native word sized). On Int#, we have the 
primitive operations (+#), (-#), (*#), negateInt#, (==#) and a couple more, 
which translate directly to the machine instructions (at least, that's the 
intention).

When you have an Int-calculation, if it's determined to be strict, GHC 
unboxes things as far as possible and carries out the calculation on the 
unboxed Int#s, wrapping the result in a I# when it's done.

So, (+#) is a little better than just a strict addition of Ints, which 
would wrap all intermediate results again in the constructor I#, only to 
immediately unbox them for the next step.

Analogous for

data Word = W# Word#

(plusWord#, minusWord#, eqWord# ...)

data Double = D# Double#

((+##), (-##), (*##), (**##), (==##), ...)

data Float = F# Float#

(plusFloat#, ...)

Most of the time, you need not worry about that, GHC's strictness analyser 
is pretty good, sometimes you need to help it with a few bang patterns or 
seq's, check the generated core (-ddump-simpl), lots of #'s and 'case's are 
good, 'let's and boxed Ints (Words, ...) are generally less desirable [in 
loops and such].
Only rarely you need to directly use the raw types and primops.

 But if you make an overlay to (+), like, say:
 
 (?) :: (Num a) = a - a - a
 a ? b = a + b
 
 Then (?) will be lazy, won't it?

Yes, generally, but

 Then optimizations will not occur, a ? b will remain a thunk and not be
 replaced by a +# b and be strictly evaluated?

Well, it's very small, so it will be inlined and you might as well directly 
write (+).
If it's used at the appropriate types, it will be replaced with (+#), 
plusWord# or whatever if (+) will be.
Add a {-# NOINLINE (?) #-} pragma or have it large enough to not be inlined 
(or recursive) and you shut out the strictness analyser (except you invite 
it in with {-# SPECIALISE #-} pragmas or so).

 
 If so, then it means that you can always turn a strict function into a
 non strict one, am I right?

Err, terminology problem here.
Strictly speaking, a function is strict iff

f _|_ = _|_

while we are talking here about evaluation strategies, so we should better 
have spoken of eager vs. deferred evaluation.
A non-strict function has different semantics from a strict one by 
definition.

If you have a strict function, you may evaluate its argument eagerly 
without changing the result¹, while eager evaluation of a non-strict 
function's argument may produce _|_ where deferred evaluation wouldn't.

By default, everything in Haskell is deferredly evaluated, but the 
strictness analyser may find that it's okay to evaluate some things eagerly 
(or the programmer indicates that eager evaluation is desired with a seq or 
bang pattern). Then 

Re: [Haskell-cafe] how to optmize this code?

2011-03-31 Thread Ryan Ingram
On Thu, Mar 31, 2011 at 7:29 AM, Daniel Fischer 
daniel.is.fisc...@googlemail.com wrote:

 Err, terminology problem here.
 Strictly speaking, a function is strict iff

 f _|_ = _|_

 while we are talking here about evaluation strategies, so we should better
 have spoken of eager vs. deferred evaluation.
 A non-strict function has different semantics from a strict one by
 definition.

 If you have a strict function, you may evaluate its argument eagerly
 without changing the result¹, while eager evaluation of a non-strict
 function's argument may produce _|_ where deferred evaluation wouldn't.


This is almost but not entirely true.  Consider

f x = error f is not implemented

Clearly, f _|_ = _|_, so f is strict.

f (error bang!)

might, depending on how strictness analysis proceeds, generate an f is not
implemented error or a bang! error.  But that's only observable at the IO
level, and the optimization is considered important enough, that potentially
generating a different exception is allowed.

I think this paper covers some of the details:
http://research.microsoft.com/en-us/um/people/simonpj/papers/imprecise-exn.htm

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] how to optmize this code?

2011-03-30 Thread Gilberto Garcia
Hi Haskellers,

I was solving this problem from project euler to study haskell.
I came up whit the following solution and I was wondering if there is
a more optimized and concise solution.

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

Thanks in advance
ggarcia

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-30 Thread Daniel Fischer
On Wednesday 30 March 2011 16:39:49, Gilberto Garcia wrote:
 Hi Haskellers,
 
 I was solving this problem from project euler to study haskell.
 I came up whit the following solution and I was wondering if there is
 a more optimized and concise solution.

Yes. There's a constant-time formula for summing the multiples of k = a 
(those are [k, 2*k .. (a `quot` k) * k], 
so the sum is k* sum [1 .. (a `quot` k)], 
try to find a formula for sum [1 .. n]), then you need the
http://en.wikipedia.org/wiki/Inclusion–exclusion_principle

If you're looking for multiples of any of few numbers, it's very simple 
then. For longer lists (say you want to sum the multiples of any of 30 
numbers), you have to be clever implementing the inclusion-exclusion 
algorithm to keep the running time low, sometimes other methods may be 
faster then (fkSum (10^7) [2 .. 30] for example).

 
 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
 
 Thanks in advance
 ggarcia

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-30 Thread Yves Parès
If I'm not wrong :

sum [1..n] = (n² + n)/2


2011/3/30 Daniel Fischer daniel.is.fisc...@googlemail.com

 On Wednesday 30 March 2011 16:39:49, Gilberto Garcia wrote:
  Hi Haskellers,
 
  I was solving this problem from project euler to study haskell.
  I came up whit the following solution and I was wondering if there is
  a more optimized and concise solution.

 Yes. There's a constant-time formula for summing the multiples of k = a
 (those are [k, 2*k .. (a `quot` k) * k],
 so the sum is k* sum [1 .. (a `quot` k)],
 try to find a formula for sum [1 .. n]), then you need the
 http://en.wikipedia.org/wiki/Inclusion–exclusion_principle

 If you're looking for multiples of any of few numbers, it's very simple
 then. For longer lists (say you want to sum the multiples of any of 30
 numbers), you have to be clever implementing the inclusion-exclusion
 algorithm to keep the running time low, sometimes other methods may be
 faster then (fkSum (10^7) [2 .. 30] for example).

 
  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
 
  Thanks in advance
  ggarcia

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-30 Thread Felipe Almeida Lessa
On Wed, Mar 30, 2011 at 2:39 PM, Gilberto Garcia giba@gmail.com wrote:
 fkSum :: Int - [Int] - Int
 fkSum a [] = 0
 fkSum a (b) = foldl (+) 0 (filter (\x - isMultiple x b) [1..a])

Daniel Fischer and Yves Parès gave you good suggestions about
implementing a different, better algorithm for you problem.  However,
there's one small thing about your current code.  Instead of foldl,
you should use foldl' (use import Data.List), which is strict in the
accumulator.  Most of the time you want foldl' instead of foldl.  You
can learn more about the list folds here [1].

HTH,

[1] http://www.haskell.org/haskellwiki/Foldr_Foldl_Foldl%27

-- 
Felipe.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to optmize this code?

2011-03-30 Thread Gilberto Garcia
Thank you very much for the suggestions.

giba

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe