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

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

The keys iterator is designed to get the key names defined in a
message.  Key names on which the iteration is carried out can be
filtered through their attributes or by the namespace they belong to.

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.KeysIterator
       ( -- *The GRIB Keys Iterator
         GribKeysIterator(..)
       , gribKeysIteratorNew
       , gribKeysIteratorNext
       , gribKeysIteratorGetName
       , gribKeysIteratorRewind
       , gribKeysIteratorDelete
       , withGribKeysIterator

         -- **Iterator flags
       , GribKeysIteratorFlag(..)
       , gribKeysIteratorSetFlags
       ) 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, throw )
import Foreign           ( nullPtr )
import Foreign.C         ( peekCString )

import Data.Grib.Raw.Exception
import Data.Grib.Raw.Handle
{-# LINE 39 "src/Data/Grib/Raw/KeysIterator.chs" #-}

import Data.Grib.Raw.Marshal




-- |Filter flags for 'GribKeysIterator'.
data GribKeysIteratorFlag = GribKeysIteratorAllKeys
                          | GribKeysIteratorSkipReadOnly
                          | GribKeysIteratorSkipOptional
                          | GribKeysIteratorSkipEditionSpecific
                          | GribKeysIteratorSkipCoded
                          | GribKeysIteratorSkipComputed
                          | GribKeysIteratorSkipDuplicates
                          | GribKeysIteratorSkipFunction
  deriving (Eq,Show)
instance Enum GribKeysIteratorFlag where
  succ GribKeysIteratorAllKeys = GribKeysIteratorSkipReadOnly
  succ GribKeysIteratorSkipReadOnly = GribKeysIteratorSkipOptional
  succ GribKeysIteratorSkipOptional = GribKeysIteratorSkipEditionSpecific
  succ GribKeysIteratorSkipEditionSpecific = GribKeysIteratorSkipCoded
  succ GribKeysIteratorSkipCoded = GribKeysIteratorSkipComputed
  succ GribKeysIteratorSkipComputed = GribKeysIteratorSkipDuplicates
  succ GribKeysIteratorSkipDuplicates = GribKeysIteratorSkipFunction
  succ GribKeysIteratorSkipFunction = error "GribKeysIteratorFlag.succ: GribKeysIteratorSkipFunction has no successor"

  pred GribKeysIteratorSkipReadOnly = GribKeysIteratorAllKeys
  pred GribKeysIteratorSkipOptional = GribKeysIteratorSkipReadOnly
  pred GribKeysIteratorSkipEditionSpecific = GribKeysIteratorSkipOptional
  pred GribKeysIteratorSkipCoded = GribKeysIteratorSkipEditionSpecific
  pred GribKeysIteratorSkipComputed = GribKeysIteratorSkipCoded
  pred GribKeysIteratorSkipDuplicates = GribKeysIteratorSkipComputed
  pred GribKeysIteratorSkipFunction = GribKeysIteratorSkipDuplicates
  pred GribKeysIteratorAllKeys = error "GribKeysIteratorFlag.pred: GribKeysIteratorAllKeys has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from GribKeysIteratorSkipFunction

  fromEnum GribKeysIteratorAllKeys = 0
  fromEnum GribKeysIteratorSkipReadOnly = 1
  fromEnum GribKeysIteratorSkipOptional = 2
  fromEnum GribKeysIteratorSkipEditionSpecific = 4
  fromEnum GribKeysIteratorSkipCoded = 8
  fromEnum GribKeysIteratorSkipComputed = 16
  fromEnum GribKeysIteratorSkipDuplicates = 32
  fromEnum GribKeysIteratorSkipFunction = 64

  toEnum 0 = GribKeysIteratorAllKeys
  toEnum 1 = GribKeysIteratorSkipReadOnly
  toEnum 2 = GribKeysIteratorSkipOptional
  toEnum 4 = GribKeysIteratorSkipEditionSpecific
  toEnum 8 = GribKeysIteratorSkipCoded
  toEnum 16 = GribKeysIteratorSkipComputed
  toEnum 32 = GribKeysIteratorSkipDuplicates
  toEnum 64 = GribKeysIteratorSkipFunction
  toEnum unmatched = error ("GribKeysIteratorFlag.toEnum: Cannot match " ++ show unmatched)

{-# LINE 56 "src/Data/Grib/Raw/KeysIterator.chs" #-}


-- typedef struct grib_keys_iterator grib_keys_iterator;
--
-- If the grib_handle used to create a grib_keys_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 keys iterator. Iterator over keys.
newtype GribKeysIterator = GribKeysIterator (C2HSImp.Ptr (GribKeysIterator)) deriving (Eq, Show)

-- grib_keys_iterator* grib_keys_iterator_new(grib_handle* h,
--                                            unsigned long filter_flags,
--                                            const char* name_space);
--
-- |Create a new iterator from a valid and initialized handle.
--
-- The returned iterator needs to be manually deleted with
-- 'gribKeysIteratorDelete'.  However, due to the reason given in that
-- function, 'withGribKeysIterator' should be preferred over this
-- function.
--
-- This operation may fail with:
--
--   * @NullPtrReturned@ if the handle is invalid or the memory
--   allocation fails.
gribKeysIteratorNew :: (GribHandle) -- ^the handle whose keys you want to iterate
 -> ([GribKeysIteratorFlag]) -- ^flags to filter out some of the keys through their  attributes
 -> (Maybe String) -- ^if not @Nothing@, the iteration is carried out only on keys  belonging to the namespace passed
 -> IO ((GribKeysIterator)) -- ^an IO action that will return the new iterator

gribKeysIteratorNew a1 a2 a3 =
  (withGribHandle) a1 $ \a1' -> 
  let {a2' = fromFlagList a2} in 
  maybeWithCString a3 $ \a3' -> 
  gribKeysIteratorNew'_ a1' a2' a3' >>= \res ->
  let {res' = checkKeysIterator res} in
  return (res')

{-# LINE 95 "src/Data/Grib/Raw/KeysIterator.chs" #-}

  where checkKeysIterator kiter@(GribKeysIterator ptr)
          | ptr == nullPtr = throw NullPtrReturned
          | otherwise      = kiter

-- int grib_keys_iterator_next(grib_keys_iterator *kiter);
--
-- |Try to step to the next key and return @True@ if successful.
gribKeysIteratorNext :: (GribKeysIterator) -> IO ((Bool))
gribKeysIteratorNext a1 =
  let {a1' = id a1} in 
  gribKeysIteratorNext'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 103 "src/Data/Grib/Raw/KeysIterator.chs" #-}


-- const char* grib_keys_iterator_get_name(grib_keys_iterator *kiter);
--
-- |Get the key name from the iterator.
gribKeysIteratorGetName :: (GribKeysIterator) -> IO ((Key))
gribKeysIteratorGetName a1 =
  let {a1' = id a1} in 
  gribKeysIteratorGetName'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 110 "src/Data/Grib/Raw/KeysIterator.chs" #-}


-- int grib_keys_iterator_delete(grib_keys_iterator* kiter);
--
-- |Delete the iterator.
--
-- 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, 'withGribKeysIterator' should be
-- preferred over directly using 'gribKeysIteratorNew' and this
-- function.
gribKeysIteratorDelete :: (GribKeysIterator) -> IO ()
gribKeysIteratorDelete a1 =
  let {a1' = id a1} in 
  gribKeysIteratorDelete'_ a1' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 123 "src/Data/Grib/Raw/KeysIterator.chs" #-}


-- int grib_keys_iterator_rewind(grib_keys_iterator* kiter);
--
-- |Rewind the iterator.
gribKeysIteratorRewind :: (GribKeysIterator) -> IO ()
gribKeysIteratorRewind a1 =
  let {a1' = id a1} in 
  gribKeysIteratorRewind'_ a1' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 130 "src/Data/Grib/Raw/KeysIterator.chs" #-}


-- int grib_keys_iterator_set_flags(grib_keys_iterator *kiter,
--                                  unsigned long flags);
--
-- |Update the flags of the iterator.
gribKeysIteratorSetFlags :: (GribKeysIterator) -> ([GribKeysIteratorFlag]) -> IO ()
gribKeysIteratorSetFlags a1 a2 =
  let {a1' = id a1} in 
  let {a2' = fromFlagList a2} in 
  gribKeysIteratorSetFlags'_ a1' a2' >>= \res ->
  checkStatus res >> 
  return ()

{-# LINE 139 "src/Data/Grib/Raw/KeysIterator.chs" #-}


-- |Safely create, use and delete a 'GribKeysIterator'.
--
-- This function should be preferred over directly using
-- 'gribKeysIteratorNew' and 'gribKeysIteratorDelete'.
--
-- This operation may fail with:
--
--   * @NullPtrReturned@ if the handle is invalid or the memory
--   allocation fails.
withGribKeysIterator :: GribHandle
                     -- ^the handle whose keys you want to iterate
                     -> [GribKeysIteratorFlag]
                     -- ^flags to filter out some of the keys through
                     -- their attributes
                     -> Maybe String
                     -- ^if not @Nothing@, the iteration is carried
                     -- out only on keys belonging to the namespace
                     -- passed
                     -> (GribKeysIterator -> IO a)
                     -- ^a function that will be called with the newly
                     -- created iterator
                     -> IO a
                     -- ^the result of the above function
withGribKeysIterator h flags ns = bracket before after
  where before      = gribKeysIteratorNew h flags ns
        after kiter = withGribHandle h $ \_ -> gribKeysIteratorDelete kiter

foreign import ccall unsafe "Data/Grib/Raw/KeysIterator.chs.h grib_keys_iterator_new"
  gribKeysIteratorNew'_ :: ((C2HSImp.Ptr (GribHandle)) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (GribKeysIterator)))))

foreign import ccall unsafe "Data/Grib/Raw/KeysIterator.chs.h grib_keys_iterator_next"
  gribKeysIteratorNext'_ :: ((GribKeysIterator) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Data/Grib/Raw/KeysIterator.chs.h grib_keys_iterator_get_name"
  gribKeysIteratorGetName'_ :: ((GribKeysIterator) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))

foreign import ccall unsafe "Data/Grib/Raw/KeysIterator.chs.h grib_keys_iterator_delete"
  gribKeysIteratorDelete'_ :: ((GribKeysIterator) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Data/Grib/Raw/KeysIterator.chs.h grib_keys_iterator_rewind"
  gribKeysIteratorRewind'_ :: ((GribKeysIterator) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Data/Grib/Raw/KeysIterator.chs.h grib_keys_iterator_set_flags"
  gribKeysIteratorSetFlags'_ :: ((GribKeysIterator) -> (C2HSImp.CULong -> (IO C2HSImp.CInt)))