Loop optimisation with identical counters

Christian Höner zu Siederdissen choener at tbi.univie.ac.at
Tue Nov 2 04:17:38 EDT 2010


Hi,

is the following problem a job for ghc or the code generation backend
(llvm)?

We are given this program:

{-# LANGUAGE BangPatterns #-}

module Main where

f :: Int -> Int -> Int -> Int -> Int
f !i !j !s !m
  | i == 0    = s+m
  | otherwise = f (i-1) (j-1) (s + i+1) (m + j*5)

g :: Int -> Int
g !k = f k k 0 0


ff :: Int -> Int -> Int -> Int
ff !i !s !m
  | i == 0    = s+m
  | otherwise = ff (i-1) (s + i+1) (m + i*5)

gg :: Int -> Int
gg !k = ff k 0 0

main = do
  print $ g 20
  print $ gg 20


Here, 'f' and 'g' are a representation of the code I have. Both counters
'i' and 'j' in 'f' count from the same value with the same step size and
terminate at the same time but are not reduced to just one counter. Can
I reasonably expect this to be done by the code generator?
'ff' represents what I would like to see.

Btw. look at the core, to see that indeed 'f' keep four arguments.
Functions like 'f' are a result of vector-fusion at work but can be
written by oneself as well. The point is that if 'f' gets reduced to
'ff' then I can have this:

fun k = zipWith (+) (map f1 $ mkIdxs k) (map f2 $ mkIdxs k)

which makes for nicer code sometimes; but before rewriting I wanted to
ask if that kills performance.


Thanks,
Christian
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20101102/90646eec/attachment-0001.bin


More information about the Glasgow-haskell-users mailing list