Hi,

I think I found a performance bug. Either that, or something is going
on that I don't understand.

I've attached an example program. Here's my session with it:

===============
ghc --make -O2 MaybeBug.hs; time ./MaybeBug +RTS -tstderr

[1 of 1] Compiling Main             ( MaybeBug.hs, MaybeBug.o )
Linking MaybeBug ...
./MaybeBug +RTS -tstderr
-1452071552
191905792
<<ghc: 800037360 bytes, 4 GCs, 40960/40960 avg/max bytes residency (1
samples), 383M in use, 0.00 INIT (0.00 elapsed), 3.96 MUT (4.36
elapsed), 0.00 GC (0.00 elapsed) :ghc>>

real    0m4.408s
user    0m3.960s
sys     0m0.448s


ghc --make -O2 MaybeBug.hs -DSLOW -no-recomp; time ./MaybeBug +RTS -tstderr
[1 of 1] Compiling Main             ( MaybeBug.hs, MaybeBug.o )
Linking MaybeBug ...
./MaybeBug +RTS -tstderr
-1452071552
191905792
<<ghc: 4000037408 bytes, 6106 GCs, 400588800/400588800 avg/max bytes
residency (2 samples), 765M in use, 0.00 INIT (0.00 elapsed), 9.71 MUT
(10.53 elapsed), 0.05 GC (0.08 elapsed) :ghc>>

real    0m10.717s
user    0m9.761s
sys     0m0.876s
==================

There are two functions, initArray1 and initArray2, that have exactly
the same implementation. I use them to initialize two arrays. If I use
initArray1 on the first, and initArray2 on the second, then things get
inlined and specialized wonderfully and no heap is used. If I use
initArray1 to initialize both arrays, then less inlining happens.
Since I'm doing possibly dangerous things with unsafePerformIO, I'm
inclined to think this is not a bug, but I'm still wondering what's
going on.

On that note: is this use of unsafePerformIO in fact dangerous? I'm
aware that allocating memory inside unsafePerformIO is not wise,
especially when that function is to be inlined. If the function body
is duplicated at the call site, I might get two identical arrays where
I could have one that is shared. I can live with that possibility, but
I'm more worried about the allocation being floated out of the
unsafePerformIO, and having unintended sharing. Can this happen, the
way I've written it? The inlining seems to be crucial for performance,
so that constructor specialization can kick in.

If there's a better way to do truly polymorphic unboxed immutable
arrays, I'm all ears. (I'm aware of Bulat's ArrayRef library, but it
doesn't seem to be maintained.. is it?)

Scott
{-# LANGUAGE CPP,BangPatterns #-}

import Foreign
import Control.Monad
import Data.ByteString.Internal

n = 100000000

main =
  let 
    a = initArray1 n (\i -> i*i)
#ifdef SLOW
    b = initArray1 n (\i -> i*i*i)
#else 
    b = initArray2 n (\i -> i*i*i)
#endif
    sumArray ar !s !i 
     | i==n = s
     | otherwise = sumArray ar (s+(ar`at`i)) (i+1)
  in 
  do
  print $ sumArray a 0 0
  print $ sumArray b 0 0


data Arr a = Arr Int (ForeignPtr a)

initArray1 size f = 
  unsafePerformIO $
    do
    fp <- mallocForeignPtrArray size  -- is this bad?
    withForeignPtr fp $ \p ->
      let init !i | i==size   = return ()
                  | otherwise = pokeElemOff p i (f i) >> init (i+1)
      in init 0
    return (Arr size fp)
{-# INLINE initArray1 #-} 

initArray2 size f = 
  unsafePerformIO $
    do
    fp <- mallocForeignPtrArray size 
    withForeignPtr fp $ \p ->
      let init !i | i==size   = return ()
                  | otherwise = pokeElemOff p i (f i) >> init (i+1)
      in init 0
    return (Arr size fp)
{-# INLINE initArray2 #-} 


at (Arr size fp) i = inlinePerformIO $ withForeignPtr fp $ \p -> peekElemOff p i
{-# INLINE at #-}
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to