module Data.Array.Parallel.Arr.BUArr (
BUArr, MBUArr,
UAE,
lengthMBU, newMBU, readMBU, writeMBU, extractMBU, copyMBU,
unsafeFreezeMBU, unsafeFreezeAllMBU,
lengthBU, emptyBU, replicateBU, indexBU, sliceBU, extractBU,
streamBU, unstreamBU,
mapBU, foldlBU, foldBU, scanlBU, scanBU, sumBU,
toBU, fromBU,
hPutBU, hGetBU
) where
import GHC.Prim (
Char#, Int#, Float#, Double#,
ByteArray#, MutableByteArray#, RealWorld,
(*#), newByteArray#, unsafeFreezeArray#, unsafeThawArray#, unsafeCoerce#,
indexWideCharArray#, readWideCharArray#, writeWideCharArray#,
indexIntArray#, readIntArray#, writeIntArray#,
indexWord8Array#, readWord8Array#, writeWord8Array#,
indexFloatArray#, readFloatArray#, writeFloatArray#,
indexDoubleArray#, readDoubleArray#, writeDoubleArray#)
import GHC.Base (
Char(..), Int(..), (+#), and#, or#, neWord#, int2Word#)
import GHC.Float (
Float(..), Double(..))
import GHC.Word ( Word8(..) )
import Data.Array.Base (
wORD_SCALE, fLOAT_SCALE, dOUBLE_SCALE)
import System.IO
import Foreign
import Foreign.C (CSize)
import GHC.Handle
import GHC.IOBase
import Data.Array.Parallel.Base
import Data.Array.Parallel.Stream
infixl 9 `indexBU`, `readMBU`
here s = "Arr.BUArr." ++ s
data BUArr e = BUArr !Int !Int ByteArray#
data MBUArr s e = MBUArr !Int (MutableByteArray# s)
instance HS e => HS (BUArr e)
instance HS e => HS (MBUArr s e)
lengthBU :: BUArr e -> Int
lengthBU (BUArr _ n _) = n
lengthMBU :: MBUArr s e -> Int
lengthMBU (MBUArr n _) = n
class HS e => UAE e where
sizeBU :: Int -> e -> Int
indexBU :: BUArr e -> Int -> e
readMBU :: MBUArr s e -> Int -> ST s e
writeMBU :: MBUArr s e -> Int -> e -> ST s ()
emptyBU :: UAE e => BUArr e
emptyBU = runST (do
a <- newMBU 0
unsafeFreezeMBU a 0
)
sliceBU :: BUArr e -> Int -> Int -> BUArr e
sliceBU (BUArr start len arr) newStart newLen =
let start' = start + newStart
in
BUArr start' ((len newStart) `min` newLen) arr
newMBU :: forall s e. UAE e => Int -> ST s (MBUArr s e)
newMBU n = ST $ \s1# ->
case sizeBU n (undefined::e) of {I# len# ->
case newByteArray# len# s1# of {(# s2#, marr# #) ->
(# s2#, MBUArr n marr# #) }}
unsafeFreezeMBU :: MBUArr s e -> Int -> ST s (BUArr e)
unsafeFreezeMBU (MBUArr m mba#) n =
checkLen (here "unsafeFreezeMBU") m n $ ST $ \s# ->
(# s#, BUArr 0 n (unsafeCoerce# mba#) #)
unsafeFreezeAllMBU :: MBUArr s e -> ST s (BUArr e)
unsafeFreezeAllMBU (MBUArr m mba#) =
ST $ \s# -> (# s#, BUArr 0 m (unsafeCoerce# mba#) #)
instance UAE () where
sizeBU _ _ = 0
indexBU (BUArr _ _ _) (I# _) = ()
readMBU (MBUArr _ _) (I# _) =
ST $ \s# ->
(# s#, () #)
writeMBU (MBUArr _ _) (I# _) () =
ST $ \s# ->
(# s#, () #)
instance UAE Bool where
sizeBU (I# n#) _ = I# n#
indexBU (BUArr (I# s#) n ba#) i@(I# i#) =
check (here "indexBU[Bool]") n i $
(indexWord8Array# ba# (s# +# i#) `neWord#` int2Word# 0#)
readMBU (MBUArr n mba#) i@(I# i#) =
check (here "readMBU[Bool]") n i $
ST $ \s# ->
case readWord8Array# mba# i# s# of {(# s2#, r# #) ->
(# s2#, r# `neWord#` int2Word# 0# #)}
writeMBU (MBUArr n mba#) i@(I# i#) e# =
checkCritical (here "writeMBU[Bool]") n i $
ST $ \s# ->
case writeWord8Array# mba# i# b# s# of {s2# ->
(# s2#, () #)}
where
b# = int2Word# (if e# then 1# else 0#)
instance UAE Char where
sizeBU (I# n#) _ = I# (cHAR_SCALE n#)
indexBU (BUArr (I# s#) n ba#) i@(I# i#) =
check (here "indexBU[Char]") n i $
case indexWideCharArray# ba# (s# +# i#) of {r# ->
(C# r#)}
readMBU (MBUArr n mba#) i@(I# i#) =
check (here "readMBU[Char]") n i $
ST $ \s# ->
case readWideCharArray# mba# i# s# of {(# s2#, r# #) ->
(# s2#, C# r# #)}
writeMBU (MBUArr n mba#) i@(I# i#) (C# e#) =
checkCritical (here "writeMBU[Char]") n i $
ST $ \s# ->
case writeWideCharArray# mba# i# e# s# of {s2# ->
(# s2#, () #)}
instance UAE Int where
sizeBU (I# n#) _ = I# (wORD_SCALE n#)
indexBU (BUArr (I# s#) n ba#) i@(I# i#) =
check (here "indexBU[Int]") n i $
case indexIntArray# ba# (s# +# i#) of {r# ->
(I# r#)}
readMBU (MBUArr n mba#) i@(I# i#) =
check (here "readMBU[Int]") n i $
ST $ \s# ->
case readIntArray# mba# i# s# of {(# s2#, r# #) ->
(# s2#, I# r# #)}
writeMBU (MBUArr n mba#) i@(I# i#) (I# e#) =
checkCritical (here "writeMBU[Int]") n i $
ST $ \s# ->
case writeIntArray# mba# i# e# s# of {s2# ->
(# s2#, () #)}
instance UAE Word8 where
sizeBU (I# n#) _ = I# n#
indexBU (BUArr (I# s#) n ba#) i@(I# i#) =
check (here "indexBU[Word8]") n i $
case indexWord8Array# ba# (s# +# i#) of {r# ->
(W8# r#)}
readMBU (MBUArr n mba#) i@(I# i#) =
check (here "readMBU[Word8]") n i $
ST $ \s# ->
case readWord8Array# mba# i# s# of {(# s2#, r# #) ->
(# s2#, W8# r# #)}
writeMBU (MBUArr n mba#) i@(I# i#) (W8# e#) =
checkCritical (here "writeMBU[Word8]") n i $
ST $ \s# ->
case writeWord8Array# mba# i# e# s# of {s2# ->
(# s2#, () #)}
instance UAE Float where
sizeBU (I# n#) _ = I# (fLOAT_SCALE n#)
indexBU (BUArr (I# s#) n ba#) i@(I# i#) =
check (here "indexBU[Float]") n i $
case indexFloatArray# ba# (s# +# i#) of {r# ->
(F# r#)}
readMBU (MBUArr n mba#) i@(I# i#) =
check (here "readMBU[Float]") n i $
ST $ \s# ->
case readFloatArray# mba# i# s# of {(# s2#, r# #) ->
(# s2#, F# r# #)}
writeMBU (MBUArr n mba#) i@(I# i#) (F# e#) =
checkCritical (here "writeMBU[Float]") n i $
ST $ \s# ->
case writeFloatArray# mba# i# e# s# of {s2# ->
(# s2#, () #)}
instance UAE Double where
sizeBU (I# n#) _ = I# (dOUBLE_SCALE n#)
indexBU (BUArr (I# s#) n ba#) i@(I# i#) =
check (here "indexBU[Double]") n i $
case indexDoubleArray# ba# (s# +# i#) of {r# ->
(D# r#)}
readMBU (MBUArr n mba#) i@(I# i#) =
check (here "readMBU[Double]") n i $
ST $ \s# ->
case readDoubleArray# mba# i# s# of {(# s2#, r# #) ->
(# s2#, D# r# #)}
writeMBU (MBUArr n mba#) i@(I# i#) (D# e#) =
checkCritical (here "writeMBU[Double]") n i $
ST $ \s# ->
case writeDoubleArray# mba# i# e# s# of {s2# ->
(# s2#, () #)}
streamBU :: UAE e => BUArr e -> Stream e
streamBU arr = Stream next 0 (lengthBU arr)
where
n = lengthBU arr
next i | i == n = Done
| otherwise = Yield (arr `indexBU` i) (i+1)
unstreamBU :: UAE e => Stream e -> BUArr e
unstreamBU (Stream next s n) =
runST (do
marr <- newMBU n
n' <- fill0 marr
unsafeFreezeMBU marr n'
)
where
fill0 marr = fill s 0
where
fill s i = i `seq`
case next s of
Done -> return i
Skip s' -> fill s' i
Yield x s' -> do
writeMBU marr i x
fill s' (i+1)
(for fontlocking)
"streamBU/unstreamBU" forall s.
streamBU (unstreamBU s) = s
#-}
replicateBU :: UAE e => Int -> e -> BUArr e
replicateBU n = unstreamBU . replicateS n
extractBU :: UAE e => BUArr e -> Int -> Int -> BUArr e
extractBU arr i n =
runST (do
ma <- newMBU n
copy0 ma
unsafeFreezeMBU ma n
)
where
fence = n `min` (lengthBU arr i)
copy0 ma = copy 0
where
copy off | off == fence = return ()
| otherwise = do
writeMBU ma off (arr `indexBU` (i + off))
copy (off + 1)
mapBU :: (UAE a, UAE b) => (a -> b) -> BUArr a -> BUArr b
mapBU f = unstreamBU . mapS f . streamBU
foldlBU :: UAE b => (a -> b -> a) -> a -> BUArr b -> a
foldlBU f z = foldS f z . streamBU
foldBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> a
foldBU = foldlBU
sumBU :: (UAE a, Num a) => BUArr a -> a
sumBU = foldBU (+) 0
scanlBU :: (UAE a, UAE b) => (a -> b -> a) -> a -> BUArr b -> BUArr a
scanlBU f z = unstreamBU . scanS f z . streamBU
scanBU :: UAE a => (a -> a -> a) -> a -> BUArr a -> BUArr a
scanBU = scanlBU
extractMBU :: UAE e => MBUArr s e -> Int -> Int -> ST s (BUArr e)
extractMBU arr i n = do
arr' <- unsafeFreezeMBU arr (i + n)
return $ extractBU arr' i n
copyMBU :: UAE e => MBUArr s e -> Int -> BUArr e -> ST s ()
copyMBU marr i arr = ins i 0
where
n = lengthBU arr
ins i j | j == n = return ()
| otherwise = do
writeMBU marr i (arr `indexBU` j)
ins (i + 1) (j + 1)
instance (Eq e, UAE e) => Eq (BUArr e) where
arr == brr = n == lengthBU brr && eq 0
where
n = lengthBU arr
eq i | i == n = True
| otherwise = (arr `indexBU` i) == (brr `indexBU` i)
&& eq (i+1)
instance (Show e, UAE e) => Show (BUArr e) where
showsPrec _ a = showString "toBU "
. showList [a `indexBU` i | i <- [0..lengthBU a 1]]
toBU :: UAE e => [e] -> BUArr e
toBU = unstreamBU . toStream
fromBU :: UAE e => BUArr e -> [e]
fromBU a = map (a `indexBU`) [0 .. lengthBU a 1]
cHAR_SCALE :: Int# -> Int#
cHAR_SCALE n# = 4# *# n#
hGetBU :: forall e. UAE e => Handle -> IO (BUArr e)
hGetBU h =
alloca $ \iptr ->
do
hGetBuf h iptr (sizeOf (undefined :: Int))
n <- peek iptr
marr@(MBUArr _ marr#) <- stToIO (newMBU n)
let bytes = sizeBU n (undefined :: e)
wantReadableHandle "hGetBU" h $
\handle@Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
buf@Buffer { bufBuf = raw, bufWPtr = w, bufRPtr = r } <- readIORef ref
let copied = bytes `min` (w r)
remaining = bytes copied
newr = r + copied
newbuf | newr == w = buf{ bufRPtr = 0, bufWPtr = 0 }
| otherwise = buf{ bufRPtr = newr }
memcpy_ba_baoff marr# raw r (fromIntegral copied)
writeIORef ref newbuf
readChunkBU fd is_stream marr# copied remaining
stToIO (unsafeFreezeAllMBU marr)
readChunkBU :: FD -> Bool -> MutableByteArray# RealWorld -> Int -> Int -> IO ()
readChunkBU fd is_stream marr# off bytes = loop off bytes
where
loop off bytes | bytes <= 0 = return ()
loop off bytes = do
r' <- readRawBuffer "readChunkBU" (fromIntegral fd) is_stream marr#
(fromIntegral off) (fromIntegral bytes)
let r = fromIntegral r'
if r == 0
then error "readChunkBU: can't read"
else loop (off + r) (bytes r)
hPutBU :: forall e. UAE e => Handle -> BUArr e -> IO ()
hPutBU h arr@(BUArr i n arr#) =
alloca $ \iptr ->
do
poke iptr n
hPutBuf h iptr (sizeOf n)
wantWritableHandle "hPutBU" h $
\handle@Handle__{ haFD=fd, haBuffer=ref, haIsStream=stream } -> do
old_buf <- readIORef ref
flushed_buf <- flushWriteBuffer fd stream old_buf
writeIORef ref flushed_buf
let this_buf = Buffer { bufBuf = unsafeCoerce# arr#
, bufState = WriteBuffer
, bufRPtr = off
, bufWPtr = off + size
, bufSize = size
}
flushWriteBuffer fd stream this_buf
return ()
where
off = sizeBU i (undefined :: e)
size = sizeBU n (undefined :: e)
foreign import ccall unsafe "__hscore_memcpy_src_off"
memcpy_ba_baoff :: RawBuffer -> RawBuffer -> Int -> CSize -> IO (Ptr ())