module Data.Grib.Raw.Iterator
(
GribIterator(..)
, gribIteratorNew
, gribIteratorNext
, gribIteratorPrevious
, gribIteratorHasNext
, gribIteratorReset
, gribIteratorDelete
, withGribIterator
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Control.Exception ( bracket )
import Foreign ( alloca )
import Data.Grib.Raw.Handle
import Data.Grib.Raw.Marshal
newtype GribIterator = GribIterator (C2HSImp.Ptr (GribIterator)) deriving (Eq, Show)
gribIteratorNew :: (GribHandle)
-> (Int)
-> IO ((GribIterator))
gribIteratorNew a1 a2 =
(withGribHandle) a1 $ \a1' ->
let {a2' = fromIntegral a2} in
alloca $ \a3' ->
gribIteratorNew'_ a1' a2' a3' >>= \res ->
let {res' = id res} in
checkStatusPtr a3'>>
return (res')
gribIteratorNext :: (GribIterator) -> IO ((Bool), (Double), (Double), (Double))
gribIteratorNext a1 =
let {a1' = id a1} in
alloca $ \a2' ->
alloca $ \a3' ->
alloca $ \a4' ->
gribIteratorNext'_ a1' a2' a3' a4' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekReal a2'>>= \a2'' ->
peekReal a3'>>= \a3'' ->
peekReal a4'>>= \a4'' ->
return (res', a2'', a3'', a4'')
gribIteratorPrevious :: (GribIterator) -> IO ((Bool), (Double), (Double), (Double))
gribIteratorPrevious a1 =
let {a1' = id a1} in
alloca $ \a2' ->
alloca $ \a3' ->
alloca $ \a4' ->
gribIteratorPrevious'_ a1' a2' a3' a4' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekReal a2'>>= \a2'' ->
peekReal a3'>>= \a3'' ->
peekReal a4'>>= \a4'' ->
return (res', a2'', a3'', a4'')
gribIteratorHasNext :: (GribIterator) -> IO ((Bool))
gribIteratorHasNext a1 =
let {a1' = id a1} in
gribIteratorHasNext'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
gribIteratorReset :: (GribIterator) -> IO ()
gribIteratorReset a1 =
let {a1' = id a1} in
gribIteratorReset'_ a1' >>= \res ->
checkStatus res >>
return ()
gribIteratorDelete :: (GribIterator) -> IO ()
gribIteratorDelete a1 =
let {a1' = id a1} in
gribIteratorDelete'_ a1' >>= \res ->
checkStatus res >>
return ()
withGribIterator :: GribHandle
-> Int
-> (GribIterator -> IO a)
-> IO a
withGribIterator h flags = bracket before after
where before = gribIteratorNew h flags
after iter = withGribHandle h $ \_ -> gribIteratorDelete iter
foreign import ccall unsafe "Data/Grib/Raw/Iterator.chs.h grib_iterator_new"
gribIteratorNew'_ :: ((C2HSImp.Ptr (GribHandle)) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO (GribIterator)))))
foreign import ccall unsafe "Data/Grib/Raw/Iterator.chs.h grib_iterator_next"
gribIteratorNext'_ :: ((GribIterator) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "Data/Grib/Raw/Iterator.chs.h grib_iterator_previous"
gribIteratorPrevious'_ :: ((GribIterator) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "Data/Grib/Raw/Iterator.chs.h grib_iterator_has_next"
gribIteratorHasNext'_ :: ((GribIterator) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Data/Grib/Raw/Iterator.chs.h grib_iterator_reset"
gribIteratorReset'_ :: ((GribIterator) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Data/Grib/Raw/Iterator.chs.h grib_iterator_delete"
gribIteratorDelete'_ :: ((GribIterator) -> (IO C2HSImp.CInt))