turn off let floating

Bernard James POPE bjpop at cs.mu.OZ.AU
Tue Apr 20 22:48:07 EDT 2004


On Thu, Apr 15, 2004 at 10:43:22AM -0700, Carl Witty wrote:
> > > However, if you have any suggestions about how to make a FAST 
> > > global counter
> > > I would be very glad to hear it. From profiling it seems like 
> > > this code
> > > is a little expensive (also it is called quite frequently).
> > 
> > You could try the FastMutInt module from GHC
> > (ghc/compiler/utils/FastMutInt.hs) to speed things up.  Unfortunately
> > unsafePerformIO has some unavoidable overhead: it can't be inlined
> > because we don't want the compiler to see its definition.
> 
> What happens if you use the FFI to call a C function like
> int getCount() { static int x; return x++; }
> and mark the function pure (outside the IO monad) and noinline? 
> (Probably all the calls get commoned up and it only gets called once;
> but it might be worth a try).

Hi all,

To test out the various possible ways of implementing a global counter
I wrote some test cases (shown below). I hope the test cases are
useful, and provide some indication of the relative performance.
However, if you spot something bogus please let me know.

Each program computes the equivalent of:

    sum ([1..100000000] :: [Int]) 

There are four different ways that I tried:

   1) pure: this is just pure functional code and should be fast. 
      This test case is only here as a control example, it is not
      a candidate solution because I need a global counter.
             
   2) ioref: this uses a global mutable counter using IORefs and
      unsafePerformIO

   3) fastMut: this uses the fast mutable integer library from GHC
      that was suggested by Simon Marlow.

   4) ffi: this implements the counter in C using the FFI.

They all run in a reasonable amount of memory so I won't report the
memory information here, just total runtime, as computed by the
unix "time" command.

Results:

   method          runtime (s)
   ---------------------------
   pure            0.7
   ffi             3.2
   fastMut         15
   ioref           23  

Note each program was compiled with ghc 6.2 with -O2 on debian linux.

One caveat is that the ffi code keeps the counter in C until the very end
of the program. This doesn't reflect the fact that I want to put each
value of the counter into a Haskell data structure, so there should be
an additional cost of turning the C int back into a Haskell Int for every
increment. I'll need to write a different test case for this aspect.

Here are the programs in the same order that they appear in the results table:

--------------------------------------------------------------------------------

   {- pure -}

   module Main where

   main = print $ loop 100000000 0

   loop :: Int -> Int -> Int
   loop 0 acc = acc
   loop n acc = loop (n-1) $! (acc + n)

--------------------------------------------------------------------------------

   /* ffi Haskell code */ 

   {-# OPTIONS -fglasgow-exts #-}

   module Main where

   -- the use of unsafe makes a big difference in runtime
   foreign import ccall unsafe "incC" inc :: Int -> ()
   foreign import ccall "getCounterC" getCounter :: Int -> IO Int

   printCounter :: IO ()
   printCounter
      = do val <- getCounter 0 -- the 0 is bogus
           print val

   main :: IO ()
   main = seq (loop 100000000) printCounter

   loop :: Int -> ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)

   /* ffi C code */

   #include "inc.h"

   int counter = 0;

   void incC (int howmuch)
   {
      counter+=howmuch;
   }

   int getCounterC (int bogus)
   {
      return counter;
   }
 
--------------------------------------------------------------------------------

   {- fastMut -}

   module Main where

   import System.IO.Unsafe (unsafePerformIO)
   import FastMutInt

   {-# NOINLINE counter #-}
   counter :: FastMutInt
   counter = unsafePerformIO newFastMutInt

   {-# NOINLINE inc #-}
   inc :: Int -> ()
   inc n = unsafePerformIO $
              do incFastMutIntBy counter n
                 return ()

   printCounter :: IO ()
   printCounter
      = do val <- readFastMutInt counter
           print val

   main :: IO ()
   main = do writeFastMutInt counter 0
             seq (loop 100000000) printCounter

   loop :: Int -> ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)

--------------------------------------------------------------------------------

   {- ioref -}

   module Main where
   
   import System.IO.Unsafe (unsafePerformIO)
   import Data.IORef (newIORef, readIORef, writeIORef, IORef)
   
   counter :: IORef Int
   {-# NOINLINE counter #-}
   counter = unsafePerformIO (newIORef 0)
   
   {-# NOINLINE inc #-}
   inc :: Int -> ()
   inc n = unsafePerformIO $
              do old <- readIORef counter
                 writeIORef counter $! old + n
   
   printCounter :: IO ()
   printCounter
      = do val <- readIORef counter
           print val
   
   main :: IO ()
   main = seq (loop 100000000) printCounter
   
   loop :: Int -> ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)  

--------------------------------------------------------------------------------


More information about the Glasgow-haskell-users mailing list