On Tue, Apr 20, 2004 at 01:59:33PM +0100, Simon Marlow wrote: > On 20 April 2004 12:48, Bernard James POPE wrote: > > > Results: > > > > method runtime (s) > > --------------------------- > > pure 0.7 > > ffi 3.2 > > fastMut 15 > > ioref 23 > > I very strongly suspect that it is the unsafePerformIO that hurts > performance in the fastMut case. Otherwise this case would be around > the same speed as the FFI example, perhaps faster. > > You could try out that theory by copying the definition of > unsafePerformIO into your code, and putting an INLINE pragma on it. I > think it's safe to do this in your case (it's not safe in general).
The time for fastMut with unsafePerformIO inlined is: 3.6 sec The code is below. Note I dropped the NOINLINE pragmas on counter and inc. This was necessary to get the fast time (is this safe?, it gives the right answer here but ...). Also I removed the constant 100000000 from the code (though it doesn't make any difference). Thanks to all who have chipped in. Cheers, Bernie. -------------------------------------------------------------------------------- {-# OPTIONS -fglasgow-exts #-} module Main where import GHC.IOBase hiding (unsafePerformIO) import FastMutInt import GHC.Base counter :: FastMutInt counter = unsafePerformIO newFastMutInt inc :: Int -> () inc n = unsafePerformIO $ do incFastMutIntBy counter n return () printCounter :: IO () printCounter = do val <- readFastMutInt counter print val main :: IO () main = do line <- getLine writeFastMutInt counter 0 seq (loop (read line)) printCounter loop :: Int -> () loop 0 = () loop n = seq (inc n) (loop $! n - 1) {-# INLINE unsafePerformIO #-} unsafePerformIO :: IO a -> a unsafePerformIO (IO m) = case m realWorld# of (# _, r #) -> r _______________________________________________ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users