-- 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/Iterator.chs" #-}
{- |
Module      : Data.Grib.Raw.Iterator
Copyright   : (c) Mattias Jakobsson 2015
License     : GPL-3

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

Iterate on latitude, longitude, values.

Most of the documentation herein was copied from the official
documentation of
<https://software.ecmwf.int/wiki/display/GRIB/Module+Index grib_api>.
-}

module Data.Grib.Raw.Iterator
       ( -- *The GRIB 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
{-# LINE 32 "src/Data/Grib/Raw/Iterator.chs" #-}

import Data.Grib.Raw.Marshal




-- typedef struct grib_iterator grib_iterator;
--
-- If the grib_handle used to create a grib_iterator has been freed
-- (garbage collected), deleting the iterator leads to undefined
-- behavior since a reference to the handle is used to access the
-- grib_context that in turn is used to free the memory.  Because of
-- this, we can't use a foreign pointer here.
--
-- |Grib iterator, structure supporting a geographic iteration of
-- values on a grib message.
newtype GribIterator = GribIterator (C2HSImp.Ptr (GribIterator)) deriving (Eq, Show)

-- grib_iterator* grib_iterator_new(grib_handle* h, unsigned long flags,
--                                  int* error);
--
-- |Create a new iterator from a handle, using current geometry and
-- values.
--
-- The returned iterator needs to be manually deleted with
-- 'gribIteratorDelete'.  However, due to the reason given in that
-- function, 'withGribIterator' should be preferred over this
-- function.
gribIteratorNew :: (GribHandle) -- ^the handle from which the iterator will be created
 -> (Int) -- ^flags for future use (ignored)
 -> IO ((GribIterator)) -- ^an IO action that will return the new iterator

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')

{-# LINE 68 "src/Data/Grib/Raw/Iterator.chs" #-}


-- int grib_iterator_next(grib_iterator *i, double* lat, double* lon,
--                        double* value);
--
-- |Get the next value from an iterator.
--
-- This function returns a tuple @(status, latitude, longitude,
-- value)@, where @status@ is @True@ if successful and @False@ if no
-- more data is available.
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'')

{-# LINE 83 "src/Data/Grib/Raw/Iterator.chs" #-}


-- int grib_iterator_previous(grib_iterator *i, double* lat, double* lon,
--                            double* value);
--
-- |Like 'gribIteratorNext', but return the previous value instead.
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'')

{-# LINE 94 "src/Data/Grib/Raw/Iterator.chs" #-}


-- int grib_iterator_has_next(grib_iterator *i);
--
-- |Test procedure for values in an iterator.
gribIteratorHasNext :: (GribIterator) -> IO ((Bool))
gribIteratorHasNext a1 =
  let {a1' = id a1} in 
  gribIteratorHasNext'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 99 "src/Data/Grib/Raw/Iterator.chs" #-}


-- int grib_iterator_reset(grib_iterator *i);
--
-- |Reset the iterator.
gribIteratorReset :: (GribIterator) -> IO ()
gribIteratorReset a1 =
  let {a1' = id a1} in 
  gribIteratorReset'_ a1' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 106 "src/Data/Grib/Raw/Iterator.chs" #-}


-- int grib_iterator_delete(grib_iterator *i);
--
-- |Frees an iterator from memory.
--
-- If the 'GribHandle' used to create the iterator has been garbage
-- collected by the time this function is called, the behavior is
-- undefined.  Because of this, 'withGribIterator' should be preferred
-- over directly using 'gribIteratorNew' and this function.
gribIteratorDelete :: (GribIterator) -> IO ()
gribIteratorDelete a1 =
  let {a1' = id a1} in 
  gribIteratorDelete'_ a1' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 118 "src/Data/Grib/Raw/Iterator.chs" #-}


-- |Safely create, use and delete a 'GribIterator'.
--
-- This function should be preferred over directly using
-- 'gribIteratorNew' and 'gribIteratorDelete'.
withGribIterator :: GribHandle
                 -- ^the handle from which the iterator will be created
                 -> Int
                 -- ^flags for future use (ignored)
                 -> (GribIterator -> IO a)
                 -- ^a function that will be called with the newly
                 -- created iterator
                 -> IO a
                 -- ^the result of the above function
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))