module Data.Grib.Raw.Handle
(
GribHandle(..)
, gribHandleNewFromFile
, gribHandleNewFromTemplate
, gribHandleNewFromSamples
, gribHandleClone
, gribWriteMessage
, withGribHandle
, gribGetMessage
, gribGetMessageCopy
, gribHandleNewFromMessage
, gribHandleNewFromMessageCopy
, gribHandleNewFromMultiMessage
, GribMultiHandle(..)
, gribMultiHandleNew
, gribMultiHandleAppend
, gribMultiHandleWrite
, withGribMultiHandle
, gribCountInFile
) where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.ForeignPtr as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Foreign
import Foreign.C
import Data.Grib.Raw.CFile
import Data.Grib.Raw.Context
import Data.Grib.Raw.Marshal
newtype GribHandle = GribHandle (C2HSImp.ForeignPtr (GribHandle))
withGribHandle :: GribHandle -> (C2HSImp.Ptr GribHandle -> IO b) -> IO b
withGribHandle (GribHandle fptr) = C2HSImp.withForeignPtr fptr
instance Eq GribHandle where
GribHandle f1 == GribHandle f2 = f1 == f2
instance Show GribHandle where
show (GribHandle f) = "GribHandle " ++ show f
checkHandle :: Ptr GribHandle -> IO GribHandle
checkHandle = checkForeignPtr GribHandle gribHandleFinalizer
gribCountInFile :: (GribContext) -> (CFilePtr) -> IO ((Int))
gribCountInFile a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
alloca $ \a3' ->
gribCountInFile'_ a1' a2' a3' >>= \res ->
checkStatus res >>
peekIntegral a3'>>= \a3'' ->
return (a3'')
gribHandleNewFromFile :: (GribContext) -> (CFilePtr) -> IO ((GribHandle))
gribHandleNewFromFile a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
alloca $ \a3' ->
gribHandleNewFromFile'_ a1' a2' a3' >>= \res ->
(\x -> C2HSImp.newForeignPtr gribHandleFinalizer x >>= (return . GribHandle)) res >>= \res' ->
checkStatusPtr a3'>>
return (res')
gribWriteMessage :: (GribHandle) -> (FilePath) -> (String) -> IO ()
gribWriteMessage a1 a2 a3 =
(withGribHandle) a1 $ \a1' ->
withCString a2 $ \a2' ->
C2HSImp.withCString a3 $ \a3' ->
gribWriteMessage'_ a1' a2' a3' >>= \res ->
checkStatus res >>
return ()
gribHandleNewFromMessage :: (GribContext) -> (Message) -> (Int) -> IO ((GribHandle))
gribHandleNewFromMessage a1 a2 a3 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromIntegral a3} in
gribHandleNewFromMessage'_ a1' a2' a3' >>= \res ->
checkHandle res >>= \res' ->
return (res')
gribHandleNewFromMultiMessage :: (GribContext) -> (Message) -> (Int) -> IO ((GribHandle), (Message), (Int))
gribHandleNewFromMultiMessage a1 a2 a3 =
let {a1' = id a1} in
with a2 $ \a2' ->
withIntegral a3 $ \a3' ->
alloca $ \a4' ->
gribHandleNewFromMultiMessage'_ a1' a2' a3' a4' >>= \res ->
(\x -> C2HSImp.newForeignPtr gribHandleFinalizer x >>= (return . GribHandle)) res >>= \res' ->
peek a2'>>= \a2'' ->
peekIntegral a3'>>= \a3'' ->
checkStatusPtr a4'>>
return (res', a2'', a3'')
gribHandleNewFromMessageCopy :: (GribContext) -> (Message) -> (Int) -> IO ((GribHandle))
gribHandleNewFromMessageCopy a1 a2 a3 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromIntegral a3} in
gribHandleNewFromMessageCopy'_ a1' a2' a3' >>= \res ->
checkHandle res >>= \res' ->
return (res')
gribHandleNewFromTemplate :: (GribContext) -> (String) -> IO ((GribHandle))
gribHandleNewFromTemplate a1 a2 =
let {a1' = id a1} in
C2HSImp.withCString a2 $ \a2' ->
gribHandleNewFromTemplate'_ a1' a2' >>= \res ->
checkHandle res >>= \res' ->
return (res')
gribHandleNewFromSamples :: (GribContext)
-> (String)
-> IO ((GribHandle))
gribHandleNewFromSamples a1 a2 =
let {a1' = id a1} in
C2HSImp.withCString a2 $ \a2' ->
gribHandleNewFromSamples'_ a1' a2' >>= \res ->
checkHandle res >>= \res' ->
return (res')
gribHandleClone :: (GribHandle) -> IO ((GribHandle))
gribHandleClone a1 =
(withGribHandle) a1 $ \a1' ->
gribHandleClone'_ a1' >>= \res ->
checkHandle res >>= \res' ->
return (res')
newtype GribMultiHandle = GribMultiHandle (C2HSImp.ForeignPtr (GribMultiHandle))
withGribMultiHandle :: GribMultiHandle -> (C2HSImp.Ptr GribMultiHandle -> IO b) -> IO b
withGribMultiHandle (GribMultiHandle fptr) = C2HSImp.withForeignPtr fptr
instance Eq GribMultiHandle where
GribMultiHandle f1 == GribMultiHandle f2 = f1 == f2
instance Show GribMultiHandle where
show (GribMultiHandle f) = "GribMultiHandle " ++ show f
checkMultiHandle :: Ptr GribMultiHandle -> IO GribMultiHandle
checkMultiHandle = checkForeignPtr GribMultiHandle gribMultiHandleFinalizer
gribMultiHandleNew :: (GribContext) -> IO ((GribMultiHandle))
gribMultiHandleNew a1 =
let {a1' = id a1} in
gribMultiHandleNew'_ a1' >>= \res ->
checkMultiHandle res >>= \res' ->
return (res')
gribMultiHandleAppend :: (GribHandle) -> (Int) -> (GribMultiHandle) -> IO ()
gribMultiHandleAppend a1 a2 a3 =
(withGribHandle) a1 $ \a1' ->
let {a2' = fromIntegral a2} in
(withGribMultiHandle) a3 $ \a3' ->
gribMultiHandleAppend'_ a1' a2' a3' >>= \res ->
checkStatus res >>
return ()
gribMultiHandleWrite :: (GribMultiHandle) -> (CFilePtr) -> IO ()
gribMultiHandleWrite a1 a2 =
(withGribMultiHandle) a1 $ \a1' ->
let {a2' = id a2} in
gribMultiHandleWrite'_ a1' a2' >>= \res ->
checkStatus res >>
return ()
gribGetMessage :: (GribHandle) -> IO ((Message), (Int))
gribGetMessage a1 =
(withGribHandle) a1 $ \a1' ->
alloca $ \a2' ->
alloca $ \a3' ->
gribGetMessage'_ a1' a2' a3' >>= \res ->
checkStatus res >>
peek a2'>>= \a2'' ->
peekIntegral a3'>>= \a3'' ->
return (a2'', a3'')
gribGetMessageCopy :: (GribHandle)
-> (Message)
-> (Int)
-> IO ((Message), (Int))
gribGetMessageCopy a1 a2 a3 =
(withGribHandle) a1 $ \a1' ->
let {a2' = id a2} in
withIntegral a3 $ \a3' ->
gribGetMessageCopy'_ a1' a2' a3' >>= \res ->
checkStatus res >>
let {a2'' = id a2'} in
peekIntegral a3'>>= \a3'' ->
return (a2'', a3'')
foreign import ccall "Data/Grib/Raw/Handle.chs.h &grib_handle_delete"
gribHandleFinalizer :: C2HSImp.FinalizerPtr GribHandle
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_count_in_file"
gribCountInFile'_ :: ((GribContext) -> ((CFilePtr) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_handle_new_from_file"
gribHandleNewFromFile'_ :: ((GribContext) -> ((CFilePtr) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO (C2HSImp.Ptr (GribHandle))))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_write_message"
gribWriteMessage'_ :: ((C2HSImp.Ptr (GribHandle)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_handle_new_from_message"
gribHandleNewFromMessage'_ :: ((GribContext) -> ((C2HSImp.Ptr ()) -> (CSize -> (IO (C2HSImp.Ptr (GribHandle))))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_handle_new_from_multi_message"
gribHandleNewFromMultiMessage'_ :: ((GribContext) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> ((C2HSImp.Ptr CSize) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO (C2HSImp.Ptr (GribHandle)))))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_handle_new_from_message_copy"
gribHandleNewFromMessageCopy'_ :: ((GribContext) -> ((C2HSImp.Ptr ()) -> (CSize -> (IO (C2HSImp.Ptr (GribHandle))))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_handle_new_from_template"
gribHandleNewFromTemplate'_ :: ((GribContext) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr (GribHandle)))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_handle_new_from_samples"
gribHandleNewFromSamples'_ :: ((GribContext) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr (GribHandle)))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_handle_clone"
gribHandleClone'_ :: ((C2HSImp.Ptr (GribHandle)) -> (IO (C2HSImp.Ptr (GribHandle))))
foreign import ccall "Data/Grib/Raw/Handle.chs.h &grib_multi_handle_delete"
gribMultiHandleFinalizer :: C2HSImp.FinalizerPtr GribMultiHandle
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_multi_handle_new"
gribMultiHandleNew'_ :: ((GribContext) -> (IO (C2HSImp.Ptr (GribMultiHandle))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_multi_handle_append"
gribMultiHandleAppend'_ :: ((C2HSImp.Ptr (GribHandle)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (GribMultiHandle)) -> (IO C2HSImp.CInt))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_multi_handle_write"
gribMultiHandleWrite'_ :: ((C2HSImp.Ptr (GribMultiHandle)) -> ((CFilePtr) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_get_message"
gribGetMessage'_ :: ((C2HSImp.Ptr (GribHandle)) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> ((C2HSImp.Ptr CSize) -> (IO C2HSImp.CInt))))
foreign import ccall safe "Data/Grib/Raw/Handle.chs.h grib_get_message_copy"
gribGetMessageCopy'_ :: ((C2HSImp.Ptr (GribHandle)) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr CSize) -> (IO C2HSImp.CInt))))