{-# LINE 1 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LANGUAGE Safe #-}
module System.Posix.SharedMem
(ShmOpenFlags(..), shmOpen, shmUnlink)
where
{-# LINE 24 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LINE 26 "libraries/unix/System/Posix/SharedMem.hsc" #-}
import System.Posix.Types
import qualified System.Posix.Internals as Base
{-# LINE 31 "libraries/unix/System/Posix/SharedMem.hsc" #-}
import Foreign.C
{-# LINE 33 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LINE 34 "libraries/unix/System/Posix/SharedMem.hsc" #-}
import Data.Bits
{-# LINE 36 "libraries/unix/System/Posix/SharedMem.hsc" #-}
data ShmOpenFlags = ShmOpenFlags
{ ShmOpenFlags -> Bool
shmReadWrite :: Bool,
ShmOpenFlags -> Bool
shmCreate :: Bool,
ShmOpenFlags -> Bool
shmExclusive :: Bool,
ShmOpenFlags -> Bool
shmTrunc :: Bool
}
shmOpen :: String -> ShmOpenFlags -> FileMode -> IO Fd
{-# LINE 51 "libraries/unix/System/Posix/SharedMem.hsc" #-}
shmOpen name flags mode =
do cflags0 <- return 0
cflags1 <- return $ cflags0 .|. (if shmReadWrite flags
then Base.o_RDWR
else Base.o_RDONLY)
cflags2 <- return $ cflags1 .|. (if shmCreate flags then Base.o_CREAT
else 0)
cflags3 <- return $ cflags2 .|. (if shmExclusive flags
then Base.o_EXCL
else 0)
cflags4 <- return $ cflags3 .|. (if shmTrunc flags then Base.o_TRUNC
else 0)
withCAString name (shmOpen' cflags4)
where shmOpen' cflags cname =
do fd <- throwErrnoIfMinus1 "shmOpen" $
shm_open cname cflags mode
return $ Fd fd
{-# LINE 72 "libraries/unix/System/Posix/SharedMem.hsc" #-}
shmUnlink :: String -> IO ()
{-# LINE 76 "libraries/unix/System/Posix/SharedMem.hsc" #-}
shmUnlink name = withCAString name shmUnlink'
where shmUnlink' cname =
throwErrnoIfMinus1_ "shmUnlink" $ shm_unlink cname
{-# LINE 83 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LINE 85 "libraries/unix/System/Posix/SharedMem.hsc" #-}
foreign import ccall unsafe "shm_open"
shm_open :: CString -> CInt -> CMode -> IO CInt
{-# LINE 88 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LINE 90 "libraries/unix/System/Posix/SharedMem.hsc" #-}
foreign import ccall unsafe "shm_unlink"
shm_unlink :: CString -> IO CInt
{-# LINE 93 "libraries/unix/System/Posix/SharedMem.hsc" #-}