{-# LINE 1 "src/Unix/C.hsc" #-}
{-# LANGUAGE InterruptibleFFI #-}
module Unix.C
    ( module X
    , c_close
    , c_fdatasync
    , c_fsync
    , c_ftruncate
    , c_mkdir
    , c_open
    , c_openat
    , c_pread
    , c_pwrite
    , c_read
    , c_remove
    , c_rmdir
    , c_write

    , c_O_APPEND
    , c_O_CLOEXEC
    , c_O_CREAT
    , c_O_DIRECTORY
    , c_O_EXCL
    , c_O_NOFOLLOW
    , c_O_NONBLOCK
    , c_O_NDELAY
    , c_O_TRUNC
    , c_O_RDONLY
    , c_O_WRONLY
    , c_O_RDWR
    ) where





import Zhp

import CString (CStr(..))
import Foreign.C.Types    as X
import Foreign.Ptr        as X
import System.Posix.Types as X

foreign import ccall interruptible "close" c_close :: Fd -> IO CInt
foreign import ccall interruptible "fdatasync" c_fdatasync :: Fd -> IO CInt
foreign import ccall interruptible "fsync" c_fsync :: Fd -> IO CInt
foreign import ccall interruptible "ftruncate" c_ftruncate :: Fd -> COff -> IO Int
foreign import ccall interruptible "mkdir" c_mkdir :: CStr -> CMode -> IO CInt
foreign import ccall interruptible "openat" c_openat :: Fd -> CStr -> CInt -> CMode -> IO Fd
foreign import ccall interruptible "open" c_open :: CStr -> CInt -> CMode -> IO Fd
foreign import ccall interruptible "pread"  c_pread  :: Fd -> Ptr Word8 -> CSize -> COff -> IO CSsize
foreign import ccall interruptible "pwrite" c_pwrite :: Fd -> Ptr Word8 -> CSize -> COff -> IO CSsize
foreign import ccall interruptible "read"  c_read :: Fd -> Ptr Word8 -> CSize -> IO CSsize
foreign import ccall interruptible "remove"  c_remove :: CStr -> IO CInt
foreign import ccall interruptible "rmdir"  c_rmdir :: CStr -> IO CInt
foreign import ccall interruptible "write" c_write :: Fd -> Ptr Word8 -> CSize -> IO CSsize

c_O_APPEND :: CInt
c_O_APPEND :: CInt
c_O_APPEND = CInt
1024
{-# LINE 59 "src/Unix/C.hsc" #-}

c_O_CLOEXEC :: CInt
c_O_CLOEXEC :: CInt
c_O_CLOEXEC = CInt
524288
{-# LINE 62 "src/Unix/C.hsc" #-}

c_O_CREAT :: CInt
c_O_CREAT :: CInt
c_O_CREAT = CInt
64
{-# LINE 65 "src/Unix/C.hsc" #-}

c_O_DIRECTORY :: CInt
c_O_DIRECTORY :: CInt
c_O_DIRECTORY = CInt
65536
{-# LINE 68 "src/Unix/C.hsc" #-}

c_O_EXCL :: CInt
c_O_EXCL :: CInt
c_O_EXCL = CInt
128
{-# LINE 71 "src/Unix/C.hsc" #-}

c_O_NOFOLLOW :: CInt
c_O_NOFOLLOW :: CInt
c_O_NOFOLLOW = CInt
131072
{-# LINE 74 "src/Unix/C.hsc" #-}

c_O_NONBLOCK :: CInt
c_O_NONBLOCK :: CInt
c_O_NONBLOCK = CInt
2048
{-# LINE 77 "src/Unix/C.hsc" #-}

c_O_NDELAY :: CInt
c_O_NDELAY :: CInt
c_O_NDELAY = CInt
2048
{-# LINE 80 "src/Unix/C.hsc" #-}

c_O_TRUNC :: CInt
c_O_TRUNC :: CInt
c_O_TRUNC = CInt
512
{-# LINE 83 "src/Unix/C.hsc" #-}

c_O_RDONLY :: CInt
c_O_RDONLY :: CInt
c_O_RDONLY = CInt
0
{-# LINE 86 "src/Unix/C.hsc" #-}

c_O_WRONLY :: CInt
c_O_WRONLY :: CInt
c_O_WRONLY = CInt
1
{-# LINE 89 "src/Unix/C.hsc" #-}

c_O_RDWR :: CInt
c_O_RDWR :: CInt
c_O_RDWR = CInt
2
{-# LINE 92 "src/Unix/C.hsc" #-}