{-# LANGUAGE MagicHash #-}
module Data.Array.Repa.Eval.Chunked
( fillLinearS
, fillBlock2S
, fillChunkedP
, fillChunkedIOP)
where
import Data.Array.Repa.Index
import Data.Array.Repa.Eval.Gang
import GHC.Exts
import Prelude as P
fillLinearS
:: Int
-> (Int -> a -> IO ())
-> (Int -> a)
-> IO ()
fillLinearS !(I# len) write getElem
= fill 0#
where fill !ix
| 1# <- ix >=# len
= return ()
| otherwise
= do write (I# ix) (getElem (I# ix))
fill (ix +# 1#)
{-# INLINE [0] fillLinearS #-}
fillBlock2S
:: (Int -> a -> IO ())
-> (DIM2 -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
fillBlock2S
write getElem
!imageWidth !x0 !y0 !w0 h0
= do fillBlock y0 ix0
where !x1 = x0 +# w0
!y1 = y0 +# h0
!ix0 = x0 +# (y0 *# imageWidth)
{-# INLINE fillBlock #-}
fillBlock !y !ix
| 1# <- y >=# y1
= return ()
| otherwise
= do fillLine1 x0 ix
fillBlock (y +# 1#) (ix +# imageWidth)
where {-# INLINE fillLine1 #-}
fillLine1 !x !ix'
| 1# <- x >=# x1
= return ()
| otherwise
= do write (I# ix') (getElem (Z :. (I# y) :. (I# x)))
fillLine1 (x +# 1#) (ix' +# 1#)
{-# INLINE [0] fillBlock2S #-}
fillChunkedP
:: Int
-> (Int -> a -> IO ())
-> (Int -> a)
-> IO ()
fillChunkedP !(I# len) write getElem
= gangIO theGang
$ \(I# thread) ->
let !start = splitIx thread
!end = splitIx (thread +# 1#)
in fill start end
where
!(I# threads) = gangSize theGang
!chunkLen = len `quotInt#` threads
!chunkLeftover = len `remInt#` threads
{-# INLINE splitIx #-}
splitIx thread
| 1# <- thread <# chunkLeftover
= thread *# (chunkLen +# 1#)
| otherwise
= thread *# chunkLen +# chunkLeftover
{-# INLINE fill #-}
fill !ix !end
| 1# <- ix >=# end
= return ()
| otherwise
= do write (I# ix) (getElem (I# ix))
fill (ix +# 1#) end
{-# INLINE [0] fillChunkedP #-}
fillChunkedIOP
:: Int
-> (Int -> a -> IO ())
-> (Int -> IO (Int -> IO a))
-> IO ()
fillChunkedIOP !(I# len) write mkGetElem
= gangIO theGang
$ \(I# thread) ->
let !start = splitIx thread
!end = splitIx (thread +# 1#)
in fillChunk thread start end
where
!(I# threads) = gangSize theGang
!chunkLen = len `quotInt#` threads
!chunkLeftover = len `remInt#` threads
{-# INLINE splitIx #-}
splitIx thread
| 1# <- thread <# chunkLeftover = thread *# (chunkLen +# 1#)
| otherwise = thread *# chunkLen +# chunkLeftover
{-# INLINE fillChunk #-}
fillChunk !thread !ixStart !ixEnd
= do getElem <- mkGetElem (I# thread)
fill getElem ixStart ixEnd
{-# INLINE fill #-}
fill !getElem !ix0 !end
= go ix0
where go !ix
| 1# <- ix >=# end
= return ()
| otherwise
= do x <- getElem (I# ix)
write (I# ix) x
go (ix +# 1#)
{-# INLINE [0] fillChunkedIOP #-}