-- GENERATED by C->Haskell Compiler, version 0.26.1 Budburst, 4 April 2015 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Data/Grib/Raw/CFile.chs" #-}
{- |
Module      : Data.Grib.Raw.CFile
Copyright   : (c) Mattias Jakobsson 2015
License     : GPL-3

Maintainer  : mjakob422@gmail.com
Stability   : unstable
Portability : portable

Open and close C streams in Haskell.
-}

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
import System.IO         (IOMode(..))




-- |A pointer to a C stream (FILE).
type CFilePtr = C2HSImp.Ptr (CFile)
{-# LINE 30 "src/Data/Grib/Raw/CFile.chs" #-}


-- This comment is inserted to help Haddock keep all docs.

-- |A constant indicating end of file.
eof :: CInt
eof = -1
{-# LINE 36 "src/Data/Grib/Raw/CFile.chs" #-}


-- FILE *fopen(const char *path, const char *mode);
--
-- This function is not macro expanded since we want to use the given
-- filename in the return value marshaller 'throwErrnoPathIfNull'.
--
-- |Like 'System.IO.openBinaryFile', but return a 'CFilePtr' instead of a
-- file 'System.IO.Handle'.
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"

-- |Close an open 'Foreign.C.CFile'.
closeCFile :: (CFilePtr) -> IO ()
closeCFile a1 =
  let {a1' = id a1} in 
  closeCFile'_ a1' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 57 "src/Data/Grib/Raw/CFile.chs" #-}

  where checkStatus r = when (r == eof) $ throwErrno "closeCFile"

-- |Like 'System.IO.withBinaryFile', but use a 'CFilePtr' instead of a file
-- 'System.IO.Handle'.
withBinaryCFile :: FilePath -> IOMode -> (CFilePtr -> IO a) -> IO a
withBinaryCFile name mode = bracket (openBinaryCFile name mode) closeCFile

foreign import ccall safe "Data/Grib/Raw/CFile.chs.h fopen"
  fopen :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (CFilePtr))))

foreign import ccall safe "Data/Grib/Raw/CFile.chs.h fclose"
  closeCFile'_ :: ((CFilePtr) -> (IO C2HSImp.CInt))