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

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

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

module Bindings.APR.LDAP 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/LDAP.hsc" #-}

c'APR_HAS_LDAP = 1
c'APR_HAS_LDAP :: (Num a) => a

{-# LINE 8 "Bindings/APR/LDAP.hsc" #-}

c'APR_HAS_NETSCAPE_LDAPSDK = 0
c'APR_HAS_NETSCAPE_LDAPSDK :: (Num a) => a

{-# LINE 10 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_SOLARIS_LDAPSDK = 0
c'APR_HAS_SOLARIS_LDAPSDK :: (Num a) => a

{-# LINE 11 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_NOVELL_LDAPSDK = 0
c'APR_HAS_NOVELL_LDAPSDK :: (Num a) => a

{-# LINE 12 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_MOZILLA_LDAPSDK = 0
c'APR_HAS_MOZILLA_LDAPSDK :: (Num a) => a

{-# LINE 13 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_OPENLDAP_LDAPSDK = 1
c'APR_HAS_OPENLDAP_LDAPSDK :: (Num a) => a

{-# LINE 14 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_MICROSOFT_LDAPSDK = 0
c'APR_HAS_MICROSOFT_LDAPSDK :: (Num a) => a

{-# LINE 15 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_TIVOLI_LDAPSDK = 0
c'APR_HAS_TIVOLI_LDAPSDK :: (Num a) => a

{-# LINE 16 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_ZOS_LDAPSDK = 0
c'APR_HAS_ZOS_LDAPSDK :: (Num a) => a

{-# LINE 17 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_OTHER_LDAPSDK = 0
c'APR_HAS_OTHER_LDAPSDK :: (Num a) => a

{-# LINE 18 "Bindings/APR/LDAP.hsc" #-}


{-# LINE 20 "Bindings/APR/LDAP.hsc" #-}

c'APR_HAS_LDAP_SSL = 1
c'APR_HAS_LDAP_SSL :: (Num a) => a

{-# LINE 22 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_LDAP_URL_PARSE = 0
c'APR_HAS_LDAP_URL_PARSE :: (Num a) => a

{-# LINE 23 "Bindings/APR/LDAP.hsc" #-}

data C'LDAP = C'LDAP

{-# LINE 25 "Bindings/APR/LDAP.hsc" #-}

c'APR_HAS_LDAPSSL_CLIENT_INIT = 0
c'APR_HAS_LDAPSSL_CLIENT_INIT :: (Num a) => a

{-# LINE 27 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_LDAPSSL_CLIENT_DEINIT = 0
c'APR_HAS_LDAPSSL_CLIENT_DEINIT :: (Num a) => a

{-# LINE 28 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_LDAPSSL_ADD_TRUSTED_CERT = 0
c'APR_HAS_LDAPSSL_ADD_TRUSTED_CERT :: (Num a) => a

{-# LINE 29 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_LDAP_START_TLS_S = 1
c'APR_HAS_LDAP_START_TLS_S :: (Num a) => a

{-# LINE 30 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_LDAP_SSLINIT = 0
c'APR_HAS_LDAP_SSLINIT :: (Num a) => a

{-# LINE 31 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_LDAPSSL_INIT = 0
c'APR_HAS_LDAPSSL_INIT :: (Num a) => a

{-# LINE 32 "Bindings/APR/LDAP.hsc" #-}
c'APR_HAS_LDAPSSL_INSTALL_ROUTINES = 0
c'APR_HAS_LDAPSSL_INSTALL_ROUTINES :: (Num a) => a

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

c'APR_LDAP_SIZELIMIT = 0
c'APR_LDAP_SIZELIMIT :: (Num a) => a

{-# LINE 35 "Bindings/APR/LDAP.hsc" #-}

data C'apr_ldap_err_t = C'apr_ldap_err_t{
{-# LINE 37 "Bindings/APR/LDAP.hsc" #-}

  c'apr_ldap_err_t'reason :: Ptr CChar
{-# LINE 38 "Bindings/APR/LDAP.hsc" #-}
,
  c'apr_ldap_err_t'msg :: Ptr CChar
{-# LINE 39 "Bindings/APR/LDAP.hsc" #-}
,
  c'apr_ldap_err_t'rc :: CInt
{-# LINE 40 "Bindings/APR/LDAP.hsc" #-}

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

{-# LINE 41 "Bindings/APR/LDAP.hsc" #-}

foreign import ccall "inline_APR_LDAP_IS_SERVER_DOWN" c'APR_LDAP_IS_SERVER_DOWN
  :: CInt -> IO CInt

{-# LINE 43 "Bindings/APR/LDAP.hsc" #-}