On Tuesday 17 June 2008, [EMAIL PROTECTED] wrote:
> I see that Dan Doel's post favoring Ptr/Addr#
> has the same allocation amounts (from +RTS -sstderr) for Ptr/Addr# and the
> MutableByteArray#
>
> Everyone else sees more allocation for Ptr/Addr# than MBA# and see MBA# as
> faster in these cases.
>
> I myself (on G4) see more allocation [just like Simon Marlow] for Ptr/Addr#
> and find it slower.  If I boost the initial memory with "-A 100m" then Ptr
> still allocated more, but the timing difference becomes quite small:

Pardon my noise, but is this still with the version of Ptr.hs that would (in 
your case) allocate a 1 million element list and traverse it twice, or the 
revision that fills the array in a loop with an Int#?

If it's the former, and Addr# is tying MutableByteArray# even with operations 
on a 40-some megabyte list (if the allocation is any indication), then the 
actual Addr# operations are probably faster for you, too. :)

I'll attach new, hopefully bug-free versions of the benchmark to this message.

Of course, without the list overhead, the ByteArr appears to allocate much 
more than Ptr for large arrays, because the n*w byte array shows up in the 
heap allocation, whereas the malloced memory does not. None of this should be 
a factor in the actual fannkuch benchmark, of course, which only allocates 3 
arrays of size 11.

Cheers,
-- Dan
{-# OPTIONS_GHC -fglasgow-exts #-}

module Main (main) where

import Prelude hiding (reverse)

import Control.Monad.ST

import GHC.ST
import GHC.Base
import GHC.Prim

import Foreign (sizeOf)

import System.Environment

reverse :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
reverse arr = go
 where
 go i j s
   | i <# j    = case readIntArray#  arr i    s of { (# s, ei #) ->
                 case readIntArray#  arr j    s of { (# s, ej #) ->
                 case writeIntArray# arr j ei s of { s ->
                 case writeIntArray# arr i ej s of { s ->
                 go (i +# 1#) (j -# 1#) s } } } }
   | otherwise = s
{-# INLINE reverse #-}

fill :: MutableByteArray# s -> Int# -> State# s -> State# s
fill arr n = go 0#
 where
 go i s
   | i <# n    = case writeIntArray# arr i i s of { s ->
                 go (i +# 1#) s }
   | otherwise = s
{-# INLINE fill #-}

bench :: Int -> Int -> ST s ()
bench (I# k) (I# n) = ST go
 where
 go s = case sizeOf (0 :: Int)        of { I# w ->
        case newByteArray# (n *# w) s of { (# s, arr #) ->
        case fill arr n s             of { s ->
         go' arr k s } } }
 go' arr = go''
  where
  go'' 0# s = (# s, () #)
  go'' k  s = case reverse arr 0# (n -# 1#) s of { s ->
              go'' (k -# 1#) s }
{-# INLINE bench #-}

main = do (k:n:_) <- map read `fmap` getArgs
          stToIO (bench k n)
          putStrLn "Done."
{-# OPTIONS_GHC -fglasgow-exts #-}

module Main (main) where

import Prelude hiding (reverse)

import Control.Monad

import GHC.Base
import GHC.IOBase
import GHC.Ptr

import Foreign

import System.Environment

reverse :: Addr# -> Int -> Int -> IO ()
reverse a (I# i) (I# j) = IO $ \s -> reverse' a i j s


reverse' a i j s
  | i <# j = case readIntOffAddr# a i s    of { (# s, x #) ->
             case readIntOffAddr# a j s    of { (# s, y #) ->
             case writeIntOffAddr# a j x s of { s ->
             case writeIntOffAddr# a i y s of { s ->
             reverse' a (i +# 1#) (j -# 1#) s }}}}
  | otherwise = (# s, () #)

bench :: Int -> Int -> IO ()
bench k n = do p@(Ptr a) <- mallocArray n :: IO (Ptr Int)
               fill a n
               replicateM_ k (reverse a 0 (n-1))
               free p

fill :: Addr# -> Int -> IO ()
fill a (I# n) = IO (go 0#)
 where
 go i s
   | i <# n    = case writeIntOffAddr# a i i s of s -> go (i +# 1#) s
   | otherwise = (# s, () #)

main = do (k:n:_) <- map read `fmap` getArgs
          bench k n
          putStrLn "Done."
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to