module Data.Repa.Eval.Generic.Par.Cursored
( fillBlock2
, fillCursoredBlock2)
where
import Data.Repa.Eval.Elt
import Data.Repa.Eval.Gang
import qualified Data.Repa.Eval.Generic.Seq.Cursored as Seq
import GHC.Exts
fillBlock2
:: Elt a
=> Gang
-> (Int# -> a -> IO ())
-> (Int# -> Int# -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
fillBlock2 :: forall a.
Elt a =>
Gang
-> (Int# -> a -> IO ())
-> (Int# -> Int# -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
fillBlock2 Gang
gang Int# -> a -> IO ()
write Int# -> Int# -> a
getElem !Int#
imageWidth !Int#
x0 !Int#
y0 !Int#
w0 Int#
h0
= Gang
-> (Int# -> a -> IO ())
-> (Int# -> Int# -> DIM2)
-> (Int# -> Int# -> DIM2 -> DIM2)
-> (DIM2 -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
forall a cursor.
Elt a =>
Gang
-> (Int# -> a -> IO ())
-> (Int# -> Int# -> cursor)
-> (Int# -> Int# -> cursor -> cursor)
-> (cursor -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
fillCursoredBlock2
Gang
gang Int# -> a -> IO ()
write
Int# -> Int# -> DIM2
makeCursor Int# -> Int# -> DIM2 -> DIM2
shiftCursor DIM2 -> a
loadCursor
Int#
imageWidth Int#
x0 Int#
y0 Int#
w0 Int#
h0
where makeCursor :: Int# -> Int# -> DIM2
makeCursor Int#
x Int#
y
= Int# -> Int# -> DIM2
DIM2 Int#
x Int#
y
{-# INLINE makeCursor #-}
shiftCursor :: Int# -> Int# -> DIM2 -> DIM2
shiftCursor Int#
x' Int#
y' (DIM2 Int#
x Int#
y)
= Int# -> Int# -> DIM2
DIM2 (Int#
x Int# -> Int# -> Int#
+# Int#
x') (Int#
y Int# -> Int# -> Int#
+# Int#
y')
{-# INLINE shiftCursor #-}
loadCursor :: DIM2 -> a
loadCursor (DIM2 Int#
x Int#
y)
= Int# -> Int# -> a
getElem Int#
x Int#
y
{-# INLINE loadCursor #-}
{-# INLINE [0] fillBlock2 #-}
data DIM2
= DIM2 Int# Int#
fillCursoredBlock2
:: Elt a
=> Gang
-> (Int# -> a -> IO ())
-> (Int# -> Int# -> cursor)
-> (Int# -> Int# -> cursor -> cursor)
-> (cursor -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
fillCursoredBlock2 :: forall a cursor.
Elt a =>
Gang
-> (Int# -> a -> IO ())
-> (Int# -> Int# -> cursor)
-> (Int# -> Int# -> cursor -> cursor)
-> (cursor -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
fillCursoredBlock2
Gang
gang Int# -> a -> IO ()
write
Int# -> Int# -> cursor
makeCursorFCB Int# -> Int# -> cursor -> cursor
shiftCursorFCB cursor -> a
getElemFCB
!Int#
imageWidth !Int#
x0 !Int#
y0 !Int#
w0 !Int#
h0
= Gang -> (Int# -> IO ()) -> IO ()
gangIO Gang
gang Int# -> IO ()
fillBlock
where
!threads :: Int#
threads = Gang -> Int#
gangSize Gang
gang
!colChunkLen :: Int#
colChunkLen = Int#
w0 Int# -> Int# -> Int#
`quotInt#` Int#
threads
!colChunkSlack :: Int#
colChunkSlack = Int#
w0 Int# -> Int# -> Int#
`remInt#` Int#
threads
colIx :: Int# -> Int#
colIx !Int#
ix
| Int#
1# <- Int#
ix Int# -> Int# -> Int#
<# Int#
colChunkSlack = Int#
x0 Int# -> Int# -> Int#
+# (Int#
ix Int# -> Int# -> Int#
*# (Int#
colChunkLen Int# -> Int# -> Int#
+# Int#
1#))
| Bool
otherwise = Int#
x0 Int# -> Int# -> Int#
+# (Int#
ix Int# -> Int# -> Int#
*# Int#
colChunkLen) Int# -> Int# -> Int#
+# Int#
colChunkSlack
{-# INLINE colIx #-}
fillBlock :: Int# -> IO ()
fillBlock :: Int# -> IO ()
fillBlock !Int#
ix
= let !x0' :: Int#
x0' = Int# -> Int#
colIx Int#
ix
!w0' :: Int#
w0' = Int# -> Int#
colIx (Int#
ix Int# -> Int# -> Int#
+# Int#
1#) Int# -> Int# -> Int#
-# Int#
x0'
!y0' :: Int#
y0' = Int#
y0
!h0' :: Int#
h0' = Int#
h0
in (Int# -> a -> IO ())
-> (Int# -> Int# -> cursor)
-> (Int# -> Int# -> cursor -> cursor)
-> (cursor -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
forall a cursor.
Elt a =>
(Int# -> a -> IO ())
-> (Int# -> Int# -> cursor)
-> (Int# -> Int# -> cursor -> cursor)
-> (cursor -> a)
-> Int#
-> Int#
-> Int#
-> Int#
-> Int#
-> IO ()
Seq.fillCursoredBlock2
Int# -> a -> IO ()
write
Int# -> Int# -> cursor
makeCursorFCB Int# -> Int# -> cursor -> cursor
shiftCursorFCB cursor -> a
getElemFCB
Int#
imageWidth Int#
x0' Int#
y0' Int#
w0' Int#
h0'
{-# INLINE fillBlock #-}
{-# INLINE [0] fillCursoredBlock2 #-}