{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}

module FileIO(FHandle,open,write,flush,close) where

import System.Posix
  ( Fd(Fd), openFd, fdWriteBuf, closeFd
  , OpenMode(WriteOnly)
#if MIN_VERSION_unix(2,8,0)
  , OpenFileFlags(creat)
#endif
  , defaultFileFlags
  , stdFileMode
  )
import Data.Word(Word8,Word32)
import Foreign(Ptr)
import Foreign.C(CInt(..))

data FHandle = FHandle Fd

-- should handle opening flags correctly
open :: FilePath -> IO FHandle
#if !MIN_VERSION_unix(2,8,0)
open :: FilePath -> IO FHandle
open FilePath
filename = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Fd -> FHandle
FHandle forall a b. (a -> b) -> a -> b
$ FilePath -> OpenMode -> Maybe FileMode -> OpenFileFlags -> IO Fd
openFd FilePath
filename OpenMode
WriteOnly (forall a. a -> Maybe a
Just FileMode
stdFileMode) OpenFileFlags
defaultFileFlags
#else
open filename = fmap FHandle $ openFd filename WriteOnly defaultFileFlags{ creat = Just stdFileMode }
#endif

write :: FHandle -> Ptr Word8 -> Word32 -> IO Word32
write :: FHandle -> Ptr Word8 -> Word32 -> IO Word32
write (FHandle Fd
fd) Ptr Word8
data' Word32
length = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Fd -> Ptr Word8 -> ByteCount -> IO ByteCount
fdWriteBuf Fd
fd Ptr Word8
data' forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
length

-- Handle error values?
flush :: FHandle -> IO ()
flush :: FHandle -> IO ()
flush (FHandle (Fd CInt
c_fd)) = CInt -> IO CInt
c_fsync CInt
c_fd forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()

foreign import ccall "fsync" c_fsync :: CInt -> IO CInt

close :: FHandle -> IO ()
close :: FHandle -> IO ()
close (FHandle Fd
fd) = Fd -> IO ()
closeFd Fd
fd