module Data.Grib.Raw.CFile
( CFilePtr
, withBinaryCFile
, openBinaryCFile
, closeCFile
, IOMode(..)
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Control.Exception ( bracket )
import Control.Monad ( when )
import Foreign.C ( CInt, CFile, throwErrno, throwErrnoPathIfNull
, withCString )
import System.IO ( IOMode(..) )
type CFilePtr = C2HSImp.Ptr (CFile)
eof :: CInt
eof = 1
openBinaryCFile :: FilePath -> IOMode -> IO CFilePtr
openBinaryCFile name mode =
withCString name $ \c_name ->
withCString mode_str $ \c_mode ->
throwErrnoPathIfNull "openBinaryCFile" name $
fopen c_name c_mode
where mode_str = case mode of
ReadMode -> "rb"
WriteMode -> "wb"
AppendMode -> "ab"
ReadWriteMode -> "r+b"
closeCFile :: (CFilePtr) -> IO ()
closeCFile a1 =
let {a1' = id a1} in
closeCFile'_ a1' >>= \res ->
checkStatus res >>
return ()
where checkStatus r = when (r == eof) $ throwErrno "closeCFile"
withBinaryCFile :: FilePath -> IOMode -> (CFilePtr -> IO a) -> IO a
withBinaryCFile name mode = bracket (openBinaryCFile name mode) closeCFile
foreign import ccall unsafe "Data/Grib/Raw/CFile.chs.h fopen"
fopen :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (CFilePtr))))
foreign import ccall unsafe "Data/Grib/Raw/CFile.chs.h fclose"
closeCFile'_ :: ((CFilePtr) -> (IO C2HSImp.CInt))