module Data.Array.Repa.Eval.Interleaved
        ( fillInterleavedP)
where
import Data.Array.Repa.Eval.Gang
import GHC.Exts
import Prelude          as P
fillInterleavedP
        :: Int                  
        -> (Int -> a -> IO ())  
        -> (Int -> a)           
        -> IO ()
fillInterleavedP !(I# len) write getElem
 =      gangIO theGang
         $  \(I# thread) -> 
              let !step    = threads
                  !start   = thread
                  !count   = elemsForThread thread
              in  fill step start count
 where
        
        !(I# threads)   = gangSize theGang
        
        !chunkLenBase   = len `quotInt#` threads
        
        !chunkLenSlack  = len `remInt#`  threads
        
        elemsForThread thread
         | thread <# chunkLenSlack = chunkLenBase +# 1#
         | otherwise               = chunkLenBase
        
        
        fill !step !ix0 !count0
         = go ix0 count0
         where
          go !ix !count
             | count <=# 0# = return ()
             | otherwise
             = do write (I# ix) (getElem (I# ix))
                  go (ix +# step) (count -# 1#)