module System.Posix.Realtime.MQueue (
MQAttributes(..),
Name,
mqOpen,
mqClose,
mqUnlink,
mqSend,
mqReceive,
mqGetAttributes,
mqSetAttributes,
mqNotify
) where
import System.IO
import System.IO.Error
import System.Posix.Realtime.RTDataTypes
import System.Posix.IO
import System.Posix.Types
import System.Posix.Error
import System.Posix.Internals
import Foreign
import Foreign.C
import Data.Bits
import Data.ByteString
import GHC.IO
import GHC.IO.Exception
import GHC.IO.Handle hiding (fdToHandle)
import qualified GHC.IO.Handle
type Name = String
data MQAttributes =
MQAttributes {
flags :: Int,
maxMsgNum :: Int,
maxMsgSize :: Int,
curNumMsgs :: Int
} deriving Show
instance Storable MQAttributes where
sizeOf (MQAttributes flags maxMsgNum maxMsgSize curNumMsgs) = (64)
alignment _ = 1
poke p_attrs (MQAttributes flags maxMsgNum maxMsgSize curNumMsgs) = do
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p_attrs flags
((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p_attrs maxMsgNum
((\hsc_ptr -> pokeByteOff hsc_ptr 16)) p_attrs maxMsgSize
((\hsc_ptr -> pokeByteOff hsc_ptr 24)) p_attrs curNumMsgs
peek p_attrs = do
flags <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p_attrs
maxMsgNum <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p_attrs
maxMsgSize <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) p_attrs
curNumMsgs <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) p_attrs
return (MQAttributes flags maxMsgNum maxMsgSize curNumMsgs)
mqOpen :: Name
-> OpenMode
-> Maybe FileMode
-> Maybe MQAttributes
-> IO Fd
mqOpen name how maybe_mode (Just attrs) = do
withCString name $ \ p_name -> do
allocaBytes (64) $ \ p_attrs -> do
poke p_attrs attrs
mqd <- throwErrnoPathIfMinus1 "mqOpen" name (c_mq_open p_name all_flags mode_w p_attrs)
return (Fd mqd)
where
all_flags = creat .|. open_mode
(creat, mode_w) = case maybe_mode of
Nothing -> (0,0)
Just x -> ((64), x)
open_mode = case how of
ReadOnly -> (0)
WriteOnly -> (1)
ReadWrite -> (2)
mqOpen name how maybe_mode Nothing = do
withCString name $ \ p_name -> do
mqd <- throwErrnoPathIfMinus1 "mqOpen" name (c_mq_open p_name all_flags mode_w nullPtr)
return (Fd mqd)
where
all_flags = creat .|. open_mode
(creat, mode_w) = case maybe_mode of
Nothing -> (0,0)
Just x -> ((64), x)
open_mode = case how of
ReadOnly -> (0)
WriteOnly -> (1)
ReadWrite -> (2)
foreign import ccall unsafe "bits/mqueue.h mq_open"
c_mq_open :: CString -> CInt -> CMode -> Ptr MQAttributes -> IO CInt
mqClose :: Fd -> IO ()
mqClose (Fd mqd) = throwErrnoIfMinus1_ "mqClose" (c_mq_close mqd)
foreign import ccall unsafe "mqueue.h mq_close"
c_mq_close :: CInt -> IO CInt
mqUnlink :: String -> IO ()
mqUnlink name = do
withCString name $ \ p_name -> do
throwErrnoPathIfMinus1 "mqUnlink" name (c_mq_unlink p_name)
return ()
foreign import ccall unsafe "mqueue.h mq_unlink"
c_mq_unlink :: CString -> IO CInt
mqGetAttributes :: Fd -> IO MQAttributes
mqGetAttributes (Fd mqd) = do
allocaBytes (64) $ \ p_attrs -> do
throwErrnoIfMinus1 "mqGetAttributes" (c_mq_getattr mqd p_attrs)
mq_attrs <- peek p_attrs
return (mq_attrs)
foreign import ccall unsafe "mqueue.h mq_getattr"
c_mq_getattr :: CInt -> Ptr MQAttributes -> IO CInt
mqSetAttributes :: Fd -> MQAttributes -> IO (MQAttributes)
mqSetAttributes (Fd mqd) newAttrs = do
allocaBytes (64) $ \ p_attrs -> do
allocaBytes (64) $ \ p_oldattrs -> do
poke p_attrs newAttrs
throwErrnoIfMinus1 "mqSetAttributes" (c_mq_setattr mqd p_attrs p_oldattrs)
oldAttrs <- peek p_oldattrs
return (oldAttrs)
foreign import ccall unsafe "mqueue.h mq_setattr"
c_mq_setattr :: CInt -> Ptr MQAttributes -> Ptr MQAttributes -> IO CInt
mqReceive :: Fd -> ByteCount -> Maybe Int -> IO (ByteString, Int)
mqReceive (Fd mqd) len (Just prio) = do
allocaBytes (fromIntegral len) $ \ p_buffer -> do
with (fromIntegral prio) $ \ p_prio -> do
rc <- throwErrnoIfMinus1 "mqReceive" (c_mq_receive mqd p_buffer (fromIntegral len) p_prio)
case fromIntegral rc of
0 -> ioError (IOError Nothing EOF "mqReceive" "EOF" Nothing Nothing)
n -> do
s <- packCStringLen (p_buffer, fromIntegral n)
return (s, n)
mqReceive (Fd mqd) len Nothing = do
allocaBytes (fromIntegral len) $ \ p_buffer -> do
rc <- throwErrnoIfMinus1 "mqReceive" (c_mq_receive mqd p_buffer (fromIntegral len) nullPtr)
case fromIntegral rc of
0 -> ioError (IOError Nothing EOF "mqReceive" "EOF" Nothing Nothing)
n -> do
s <- packCStringLen (p_buffer, fromIntegral n)
return (s, n)
foreign import ccall unsafe "mqueue.h mq_receive"
c_mq_receive :: CInt -> Ptr CChar -> CSize -> Ptr CInt -> IO CInt
mqSend :: Fd -> ByteString -> ByteCount -> Int -> IO ()
mqSend (Fd mqd) msg len prio = do
useAsCString msg $ \ p_msg -> do
throwErrnoIfMinus1 "mqSend" (c_mq_send mqd p_msg (fromIntegral len) (fromIntegral prio))
return ()
foreign import ccall unsafe "mqueue.h mq_send"
c_mq_send :: CInt -> Ptr CChar -> CSize -> CInt -> IO CInt
mqNotify :: Fd -> Maybe Sigevent -> IO ()
mqNotify (Fd mqd) Nothing = do
throwErrnoIfMinus1 "mqNotify" (c_mq_notify mqd nullPtr)
return ()
mqNotify (Fd mqd) (Just sigEvent) = do
allocaBytes (64) $ \ p_sigevent -> do
poke p_sigevent sigEvent
throwErrnoIfMinus1 "mqNotify" (c_mq_notify mqd p_sigevent)
return ()
foreign import ccall unsafe "mqueue.h mq_notify"
c_mq_notify :: CInt -> Ptr Sigevent -> IO CInt