[Haskell-cafe] "sum" in hmatrix and blas?
Don Stewart
dons at galois.com
Sun Jun 8 14:33:35 EDT 2008
xj2106:
> Tomas Andersson <toman144 at student.liu.se> writes:
>
> > You can never go wrong with a good old fashioned hand written tail recursion
> > when you're in doubt, they are pretty much the closest thing to for-loops
> > there is in haskell and should be easy to grok for Imperative programmers and
> > usually produce really fast code.
> >
> > sum vect = let d = dim vect
> > in sum' (d - 1) 0
> > where sum' 0 s = s + (vect @> 0)
> > sum' index s = sum' (index - 1) (s + (vect @> index))
> >
>
> Do I need the strict version of sum'? Put something like
>
> sum' a b | a `seq` b `seq` False = undefined
>
> Or ghc will optimize it automatically? I always don't know
> when such optimization is useful.
If you give a type annotation, so GHC can tell its an atomic type, like
Int or Double, 's' will be inferred as strict. But if in doubt, use bang
patterns:
{-# LANGUAGE BangPatterns #-}
sum vect = sum' (d-1) 0
where
d = dim vect
go :: Int -> Double -> Double -- for example
go 0 s = s + (vect @> 0)
go !i !s = go (i-1) (s + (vect @> i))
See this recent post on understanding how these kind of loops are compiled,
http://cgi.cse.unsw.edu.au/~dons/blog/2008/05/16
The core for your loop should look very good, assuming @> is efficient.
-- Don
More information about the Haskell-Cafe
mailing list