{-# LINE 1 "Bindings/APR/GetOpt.hsc" #-}

{-# LINE 2 "Bindings/APR/GetOpt.hsc" #-}

{-# LINE 3 "Bindings/APR/GetOpt.hsc" #-}

module Bindings.APR.GetOpt where
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 6 "Bindings/APR/GetOpt.hsc" #-}
import Bindings.APR.ErrNo
import Bindings.APR.Pools

-- apr_getopt_err_fn_t takes varargs so it can't be declared as FunPtr.
data C'apr_getopt_err_fn_t = C'apr_getopt_err_fn_t

{-# LINE 11 "Bindings/APR/GetOpt.hsc" #-}

data C'apr_getopt_t = C'apr_getopt_t{
{-# LINE 13 "Bindings/APR/GetOpt.hsc" #-}

  c'apr_getopt_t'cont :: Ptr C'apr_pool_t
{-# LINE 14 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'errfn :: Ptr C'apr_getopt_err_fn_t
{-# LINE 15 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'errarg :: Ptr ()
{-# LINE 16 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'ind :: CInt
{-# LINE 17 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'opt :: CInt
{-# LINE 18 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'reset :: CInt
{-# LINE 19 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'argc :: CInt
{-# LINE 20 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'argv :: Ptr (Ptr CChar)
{-# LINE 21 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'place :: Ptr CChar
{-# LINE 22 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'interleave :: CInt
{-# LINE 23 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'skip_start :: CInt
{-# LINE 24 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_t'skip_end :: CInt
{-# LINE 25 "Bindings/APR/GetOpt.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'apr_getopt_t where
  sizeOf _ = 48
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 40
    v11 <- peekByteOff p 44
    return $ C'apr_getopt_t v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11
  poke p (C'apr_getopt_t v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    pokeByteOff p 36 v9
    pokeByteOff p 40 v10
    pokeByteOff p 44 v11
    return ()

{-# LINE 26 "Bindings/APR/GetOpt.hsc" #-}

data C'apr_getopt_option_t = C'apr_getopt_option_t{
{-# LINE 28 "Bindings/APR/GetOpt.hsc" #-}

  c'apr_getopt_option_t'name :: Ptr CChar
{-# LINE 29 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_option_t'optch :: CInt
{-# LINE 30 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_option_t'has_arg :: CInt
{-# LINE 31 "Bindings/APR/GetOpt.hsc" #-}
,
  c'apr_getopt_option_t'description :: Ptr CChar
{-# LINE 32 "Bindings/APR/GetOpt.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'apr_getopt_option_t where
  sizeOf _ = 16
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    return $ C'apr_getopt_option_t v0 v1 v2 v3
  poke p (C'apr_getopt_option_t v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    return ()

{-# LINE 33 "Bindings/APR/GetOpt.hsc" #-}

foreign import ccall "apr_getopt_init" c'apr_getopt_init
  :: Ptr (Ptr C'apr_getopt_t) -> Ptr C'apr_pool_t -> CInt -> Ptr (Ptr CChar) -> IO C'apr_status_t
foreign import ccall "&apr_getopt_init" p'apr_getopt_init
  :: FunPtr (Ptr (Ptr C'apr_getopt_t) -> Ptr C'apr_pool_t -> CInt -> Ptr (Ptr CChar) -> IO C'apr_status_t)

{-# LINE 35 "Bindings/APR/GetOpt.hsc" #-}
foreign import ccall "apr_getopt" c'apr_getopt
  :: Ptr C'apr_getopt_t -> Ptr CChar -> Ptr CChar -> Ptr (Ptr CChar) -> IO C'apr_status_t
foreign import ccall "&apr_getopt" p'apr_getopt
  :: FunPtr (Ptr C'apr_getopt_t -> Ptr CChar -> Ptr CChar -> Ptr (Ptr CChar) -> IO C'apr_status_t)

{-# LINE 36 "Bindings/APR/GetOpt.hsc" #-}
foreign import ccall "apr_getopt_long" c'apr_getopt_long
  :: Ptr C'apr_getopt_t -> Ptr C'apr_getopt_option_t -> Ptr CInt -> Ptr (Ptr CChar) -> IO C'apr_status_t
foreign import ccall "&apr_getopt_long" p'apr_getopt_long
  :: FunPtr (Ptr C'apr_getopt_t -> Ptr C'apr_getopt_option_t -> Ptr CInt -> Ptr (Ptr CChar) -> IO C'apr_status_t)

{-# LINE 37 "Bindings/APR/GetOpt.hsc" #-}