module Data.Repa.IO.Array
( hGetArray, hGetArrayPre
, hPutArray
, hGetArrayFromCSV
, hPutArrayAsCSV)
where
import Data.Repa.Fusion.Unpack
import Data.Repa.Array.Material.Foreign
import Data.Repa.Array.Material.Boxed as A
import Data.Repa.Array.Material.Nested as A
import Data.Repa.Array as A
import qualified Foreign.Ptr as F
import qualified Foreign.ForeignPtr as F
import qualified Foreign.Marshal.Alloc as F
import qualified Foreign.Marshal.Utils as F
import System.IO
import Data.Word
import Data.Char
hGetArray :: Handle -> Int -> IO (Array F Word8)
hGetArray h len
= do
buf :: F.Ptr Word8 <- F.mallocBytes len
bytesRead <- hGetBuf h buf len
fptr <- F.newForeignPtr F.finalizerFree buf
return $ fromForeignPtr bytesRead fptr
hGetArrayPre :: Handle -> Int -> Array F Word8 -> IO (Array F Word8)
hGetArrayPre h len (toForeignPtr -> (offset,lenPre,fptrPre))
= F.withForeignPtr fptrPre
$ \ptrPre' -> do
let ptrPre = F.plusPtr ptrPre' offset
ptrBuf :: F.Ptr Word8 <- F.mallocBytes (lenPre + len)
F.copyBytes ptrBuf ptrPre lenPre
lenRead <- hGetBuf h (F.plusPtr ptrBuf lenPre) len
let bytesTotal = lenPre + lenRead
fptrBuf <- F.newForeignPtr F.finalizerFree ptrBuf
return $ fromForeignPtr bytesTotal fptrBuf
hPutArray :: Handle -> Array F Word8 -> IO ()
hPutArray h (toForeignPtr -> (offset,lenPre,fptr))
= F.withForeignPtr fptr
$ \ptr' -> do
let ptr = F.plusPtr ptr' offset
hPutBuf h ptr lenPre
hGetArrayFromCSV
:: Handle
-> IO (Array N (Array N (Array F Char)))
hGetArrayFromCSV !hIn
= do
start <- hTell hIn
hSeek hIn SeekFromEnd 0
end <- hTell hIn
let !len = end start
hSeek hIn AbsoluteSeek start
!arr8 <- hGetArray hIn (fromIntegral len)
let !nc = fromIntegral $ ord ','
let !nl = fromIntegral $ ord '\n'
let !arrSep = A.diceSep nc nl arr8
let !arrChar
= A.mapElems
(A.mapElems (A.computeS F . A.map (chr . fromIntegral)))
arrSep
return arrChar
hPutArrayAsCSV
:: ( BulkI l1 (Array l2 (Array l3 Char))
, BulkI l2 (Array l3 Char)
, BulkI l3 Char
, Unpack (Array l3 Char) t)
=> Handle
-> Array l1 (Array l2 (Array l3 Char))
-> IO ()
hPutArrayAsCSV !hOut !arrChar
= do
let !arrC = A.fromList U [',']
let !arrNL = A.fromList U ['\n']
let !arrOut
= A.mapS F (fromIntegral . ord)
$ A.concat U
$ A.mapS B (\arrFields
-> A.concat U $ A.fromList B
[ A.intercalate U arrC arrFields, arrNL])
$ arrChar
hPutArray hOut arrOut