module System.Posix.Realtime.Aio (
AIOCB,
makeAIOCB,
aioRead,
aioWrite,
aioReturn,
aioError,
aioCancel,
SyncOp(..),
aioFsync,
aioSuspend,
ListIOMode,
lioListIO,
) where
import System.IO
import System.IO.Error
import System.Posix.Realtime.RTDataTypes
import System.Posix.Types
import System.Posix.Error
import System.Posix.Internals
import Foreign
import Foreign.C
import Data.Bits
import GHC.IO
import GHC.IO.Handle hiding (fdToHandle)
import qualified GHC.IO.Handle
data AIOCBStruct
type AIOCB = ForeignPtr AIOCBStruct
aioRead :: AIOCB -> IO ()
aioRead p_aiocb = do
withForeignPtr p_aiocb $ \ p_aiocb -> do
throwErrnoIfMinus1 "aioRead" (c_aio_read p_aiocb)
return ()
foreign import ccall safe "aio.h aio_read"
c_aio_read :: Ptr AIOCBStruct -> IO CInt
aioWrite :: AIOCB -> IO ()
aioWrite p_aiocb = do
withForeignPtr p_aiocb $ \ p_aiocb -> do
throwErrnoIfMinus1 "aioWrite" (c_aio_write p_aiocb)
return ()
foreign import ccall safe "aio.h aio_write"
c_aio_write :: Ptr AIOCBStruct -> IO CInt
aioReturn :: AIOCB -> IO ByteCount
aioReturn p_aiocb = do
withForeignPtr p_aiocb $ \ p_aiocb -> do
count <- (c_aio_return p_aiocb)
return (fromIntegral count)
foreign import ccall safe "aio.h aio_return"
c_aio_return :: Ptr AIOCBStruct -> IO CInt
aioError :: AIOCB -> IO Errno
aioError p_aiocb = do
withForeignPtr p_aiocb $ \ p_aiocb -> do
errno <- (c_aio_error p_aiocb)
return (Errno errno)
foreign import ccall safe "aio.h aio_error"
c_aio_error :: Ptr AIOCBStruct -> IO CInt
aioCancel :: Fd -> AIOCB -> IO ()
aioCancel (Fd fd) p_aiocb = do
withForeignPtr p_aiocb $ \ p_aiocb -> do
throwErrnoIfMinus1 "aioCancel" (c_aio_cancel fd p_aiocb)
return ()
foreign import ccall safe "aio.h aio_cancel"
c_aio_cancel :: CInt -> Ptr AIOCBStruct -> IO CInt
data SyncOp = DSync | Sync
aioFsync :: SyncOp -> AIOCB -> IO ()
aioFsync DSync p_aiocb = do
withForeignPtr p_aiocb $ \ p_aiocb -> do
throwErrnoIfMinus1 "aioFsync" (c_aio_fsync (4096) p_aiocb)
return ()
aioFsync Sync p_aiocb = do
withForeignPtr p_aiocb $ \ p_aiocb -> do
throwErrnoIfMinus1 "aioFsync" (c_aio_fsync (1052672) p_aiocb)
return ()
foreign import ccall safe "aio.h aio_fsync"
c_aio_fsync :: CInt -> Ptr AIOCBStruct -> IO CInt
type ListIOMode = Int
lioListIO :: ListIOMode -> [AIOCB] -> Sigevent -> IO ()
lioListIO mode [] sigEvent = return ()
lioListIO mode aiocbs sigEvent = do
let numAiocbs = length aiocbs
p_aiocbs <- mapM foreignPtrToPtr aiocbs
p_p_aiocbs <- newArray p_aiocbs
allocaBytes (64) $ \ p_sigevent -> do
poke p_sigevent sigEvent
throwErrnoIfMinus1 "lioListIO" (c_lio_listio (fromIntegral mode) p_p_aiocbs (fromIntegral numAiocbs) p_sigevent)
return ()
foreign import ccall safe "aio.h lio_listio"
c_lio_listio :: CInt -> Ptr (Ptr AIOCBStruct) -> CInt -> Ptr Sigevent -> IO CInt
aioSuspend :: [AIOCB] -> TimeSpec -> IO ()
aioSuspend [] timeSpec = return ()
aioSuspend aiocbs timeSpec = do
let numAiocbs = length aiocbs
p_aiocbs <- mapM foreignPtrToPtr aiocbs
p_p_aiocbs <- newArray p_aiocbs
allocaBytes (16) $ \ p_timespec -> do
poke p_timespec timeSpec
throwErrnoIfMinus1 "aioSuspend" (c_aio_suspend p_p_aiocbs (fromIntegral numAiocbs) p_timespec)
return ()
foreign import ccall safe "aio.h aio_suspend"
c_aio_suspend :: Ptr (Ptr AIOCBStruct) -> CInt -> Ptr TimeSpec -> IO CInt
makeAIOCB :: Fd -> Int -> Int -> FileOffset -> Ptr Word8 -> ByteCount -> Sigevent -> IO AIOCB
makeAIOCB fd lioOpcode reqPrio fileOffset buffer byteCount sigEvent = do
fptr <- mallocForeignPtrBytes (168)
withForeignPtr fptr $ \ptr -> do
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) ptr fd
((\hsc_ptr -> pokeByteOff hsc_ptr 4)) ptr lioOpcode
((\hsc_ptr -> pokeByteOff hsc_ptr 8)) ptr reqPrio
((\hsc_ptr -> pokeByteOff hsc_ptr 128)) ptr fileOffset
((\hsc_ptr -> pokeByteOff hsc_ptr 16)) ptr buffer
((\hsc_ptr -> pokeByteOff hsc_ptr 24)) ptr byteCount
((\hsc_ptr -> pokeByteOff hsc_ptr 32)) ptr sigEvent
return (fptr)
foreignPtrToPtr :: ForeignPtr AIOCBStruct -> IO (Ptr AIOCBStruct)
foreignPtrToPtr fptr = do
withForeignPtr fptr return