{-# 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
{-# LINE 30 "libraries/unix/System/Posix/SharedMem.hsc" #-}
import Foreign.C
{-# LINE 32 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LINE 33 "libraries/unix/System/Posix/SharedMem.hsc" #-}
import Data.Bits
{-# LINE 35 "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 50 "libraries/unix/System/Posix/SharedMem.hsc" #-}
shmOpen name flags mode =
    do cflags0 <- return 0
       cflags1 <- return $ cflags0 .|. (if shmReadWrite flags
                                        then 2
{-# LINE 54 "libraries/unix/System/Posix/SharedMem.hsc" #-}
                                        else 0)
{-# LINE 55 "libraries/unix/System/Posix/SharedMem.hsc" #-}
       cflags2 <- return $ cflags1 .|. (if shmCreate flags then 64
{-# LINE 56 "libraries/unix/System/Posix/SharedMem.hsc" #-}
                                        else 0)
       cflags3 <- return $ cflags2 .|. (if shmExclusive flags
                                        then 128
{-# LINE 59 "libraries/unix/System/Posix/SharedMem.hsc" #-}
                                        else 0)
       cflags4 <- return $ cflags3 .|. (if shmTrunc flags then 512
{-# LINE 61 "libraries/unix/System/Posix/SharedMem.hsc" #-}
                                        else 0)
       withCAString name (shmOpen' cflags4)
    where shmOpen' cflags cname =
              do fd <- throwErrnoIfMinus1 "shmOpen" $
                       shm_open cname cflags mode
                 return $ Fd fd
{-# LINE 71 "libraries/unix/System/Posix/SharedMem.hsc" #-}
shmUnlink :: String -> IO ()
{-# LINE 75 "libraries/unix/System/Posix/SharedMem.hsc" #-}
shmUnlink name = withCAString name shmUnlink'
    where shmUnlink' cname =
              throwErrnoIfMinus1_ "shmUnlink" $ shm_unlink cname
{-# LINE 82 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LINE 84 "libraries/unix/System/Posix/SharedMem.hsc" #-}
foreign import ccall unsafe "shm_open"
        shm_open :: CString -> CInt -> CMode -> IO CInt
{-# LINE 87 "libraries/unix/System/Posix/SharedMem.hsc" #-}
{-# LINE 89 "libraries/unix/System/Posix/SharedMem.hsc" #-}
foreign import ccall unsafe "shm_unlink"
        shm_unlink :: CString -> IO CInt
{-# LINE 92 "libraries/unix/System/Posix/SharedMem.hsc" #-}