{-# LINE 1 "Bindings/Libgit2/Repository.hsc" #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LINE 2 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 3 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 4 "Bindings/Libgit2/Repository.hsc" #-}
module Bindings.Libgit2.Repository where
import Foreign.Ptr
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 7 "Bindings/Libgit2/Repository.hsc" #-}

import Bindings.Libgit2.Common
import Bindings.Libgit2.Types
import Bindings.Libgit2.Oid
foreign import ccall "git_repository_open" c'git_repository_open
  :: Ptr (Ptr C'git_repository) -> CString -> IO (CInt)
foreign import ccall "&git_repository_open" p'git_repository_open
  :: FunPtr (Ptr (Ptr C'git_repository) -> CString -> IO (CInt))

{-# LINE 12 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_wrap_odb" c'git_repository_wrap_odb
  :: Ptr (Ptr C'git_repository) -> Ptr C'git_odb -> IO (CInt)
foreign import ccall "&git_repository_wrap_odb" p'git_repository_wrap_odb
  :: FunPtr (Ptr (Ptr C'git_repository) -> Ptr C'git_odb -> IO (CInt))

{-# LINE 13 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_discover" c'git_repository_discover
  :: CString -> CSize -> CString -> CInt -> CString -> IO (CInt)
foreign import ccall "&git_repository_discover" p'git_repository_discover
  :: FunPtr (CString -> CSize -> CString -> CInt -> CString -> IO (CInt))

{-# LINE 14 "Bindings/Libgit2/Repository.hsc" #-}
{- typedef enum {
            GIT_REPOSITORY_OPEN_NO_SEARCH = 1 << 0,
            GIT_REPOSITORY_OPEN_CROSS_FS = 1 << 1
        } git_repository_open_flag_t; -}
type C'git_repository_open_flag_t = CUInt

{-# LINE 19 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_OPEN_NO_SEARCH = 1
c'GIT_REPOSITORY_OPEN_NO_SEARCH :: (Num a) => a

{-# LINE 20 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_OPEN_CROSS_FS = 2
c'GIT_REPOSITORY_OPEN_CROSS_FS :: (Num a) => a

{-# LINE 21 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_open_ext" c'git_repository_open_ext
  :: Ptr (Ptr C'git_repository) -> CString -> CUInt -> CString -> IO (CInt)
foreign import ccall "&git_repository_open_ext" p'git_repository_open_ext
  :: FunPtr (Ptr (Ptr C'git_repository) -> CString -> CUInt -> CString -> IO (CInt))

{-# LINE 22 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_new" c'git_repository_new
  :: Ptr (Ptr C'git_repository) -> IO (CInt)
foreign import ccall "&git_repository_new" p'git_repository_new
  :: FunPtr (Ptr (Ptr C'git_repository) -> IO (CInt))

{-# LINE 23 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_free" c'git_repository_free
  :: Ptr C'git_repository -> IO ()
foreign import ccall "&git_repository_free" p'git_repository_free
  :: FunPtr (Ptr C'git_repository -> IO ())

{-# LINE 24 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_init" c'git_repository_init
  :: Ptr (Ptr C'git_repository) -> CString -> CUInt -> IO (CInt)
foreign import ccall "&git_repository_init" p'git_repository_init
  :: FunPtr (Ptr (Ptr C'git_repository) -> CString -> CUInt -> IO (CInt))

{-# LINE 25 "Bindings/Libgit2/Repository.hsc" #-}
{- typedef enum {
            GIT_REPOSITORY_INIT_BARE = 1u << 0,
            GIT_REPOSITORY_INIT_NO_REINIT = 1u << 1,
            GIT_REPOSITORY_INIT_NO_DOTGIT_DIR = 1u << 2,
            GIT_REPOSITORY_INIT_MKDIR = 1u << 3,
            GIT_REPOSITORY_INIT_MKPATH = 1u << 4,
            GIT_REPOSITORY_INIT_EXTERNAL_TEMPLATE = 1u << 5
        } git_repository_init_flag_t; -}
type C'git_repository_init_flag_t = CUInt

{-# LINE 34 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_BARE = 1
c'GIT_REPOSITORY_INIT_BARE :: (Num a) => a

{-# LINE 35 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_NO_REINIT = 2
c'GIT_REPOSITORY_INIT_NO_REINIT :: (Num a) => a

{-# LINE 36 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_NO_DOTGIT_DIR = 4
c'GIT_REPOSITORY_INIT_NO_DOTGIT_DIR :: (Num a) => a

{-# LINE 37 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_MKDIR = 8
c'GIT_REPOSITORY_INIT_MKDIR :: (Num a) => a

{-# LINE 38 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_MKPATH = 16
c'GIT_REPOSITORY_INIT_MKPATH :: (Num a) => a

{-# LINE 39 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_EXTERNAL_TEMPLATE = 32
c'GIT_REPOSITORY_INIT_EXTERNAL_TEMPLATE :: (Num a) => a

{-# LINE 40 "Bindings/Libgit2/Repository.hsc" #-}
{- typedef enum {
            GIT_REPOSITORY_INIT_SHARED_UMASK = 0,
            GIT_REPOSITORY_INIT_SHARED_GROUP = 02775,
            GIT_REPOSITORY_INIT_SHARED_ALL = 02777
        } git_repository_init_mode_t; -}
type C'git_repository_init_mode_t = CUInt

{-# LINE 46 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_SHARED_UMASK = 0
c'GIT_REPOSITORY_INIT_SHARED_UMASK :: (Num a) => a

{-# LINE 47 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_SHARED_GROUP = 1533
c'GIT_REPOSITORY_INIT_SHARED_GROUP :: (Num a) => a

{-# LINE 48 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_INIT_SHARED_ALL = 1535
c'GIT_REPOSITORY_INIT_SHARED_ALL :: (Num a) => a

{-# LINE 49 "Bindings/Libgit2/Repository.hsc" #-}
{- typedef struct {
            unsigned int version;
            uint32_t flags;
            uint32_t mode;
            const char * workdir_path;
            const char * description;
            const char * template_path;
            const char * initial_head;
            const char * origin_url;
        } git_repository_init_options; -}

{-# LINE 60 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 61 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 62 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 63 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 64 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 65 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 66 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 67 "Bindings/Libgit2/Repository.hsc" #-}

{-# LINE 68 "Bindings/Libgit2/Repository.hsc" #-}
data C'git_repository_init_options = C'git_repository_init_options{
  c'git_repository_init_options'version :: CUInt,
  c'git_repository_init_options'flags :: CUInt,
  c'git_repository_init_options'mode :: CUInt,
  c'git_repository_init_options'workdir_path :: CString,
  c'git_repository_init_options'description :: CString,
  c'git_repository_init_options'template_path :: CString,
  c'git_repository_init_options'initial_head :: CString,
  c'git_repository_init_options'origin_url :: CString
} deriving (Eq,Show)
p'git_repository_init_options'version p = plusPtr p 0
p'git_repository_init_options'version :: Ptr (C'git_repository_init_options) -> Ptr (CUInt)
p'git_repository_init_options'flags p = plusPtr p 4
p'git_repository_init_options'flags :: Ptr (C'git_repository_init_options) -> Ptr (CUInt)
p'git_repository_init_options'mode p = plusPtr p 8
p'git_repository_init_options'mode :: Ptr (C'git_repository_init_options) -> Ptr (CUInt)
p'git_repository_init_options'workdir_path p = plusPtr p 16
p'git_repository_init_options'workdir_path :: Ptr (C'git_repository_init_options) -> Ptr (CString)
p'git_repository_init_options'description p = plusPtr p 24
p'git_repository_init_options'description :: Ptr (C'git_repository_init_options) -> Ptr (CString)
p'git_repository_init_options'template_path p = plusPtr p 32
p'git_repository_init_options'template_path :: Ptr (C'git_repository_init_options) -> Ptr (CString)
p'git_repository_init_options'initial_head p = plusPtr p 40
p'git_repository_init_options'initial_head :: Ptr (C'git_repository_init_options) -> Ptr (CString)
p'git_repository_init_options'origin_url p = plusPtr p 48
p'git_repository_init_options'origin_url :: Ptr (C'git_repository_init_options) -> Ptr (CString)
instance Storable C'git_repository_init_options where
  sizeOf _ = 56
  alignment _ = 8
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 16
    v4 <- peekByteOff p 24
    v5 <- peekByteOff p 32
    v6 <- peekByteOff p 40
    v7 <- peekByteOff p 48
    return $ C'git_repository_init_options v0 v1 v2 v3 v4 v5 v6 v7
  poke p (C'git_repository_init_options v0 v1 v2 v3 v4 v5 v6 v7) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 16 v3
    pokeByteOff p 24 v4
    pokeByteOff p 32 v5
    pokeByteOff p 40 v6
    pokeByteOff p 48 v7
    return ()

{-# LINE 69 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_init_ext" c'git_repository_init_ext
  :: Ptr (Ptr C'git_repository) -> CString -> Ptr C'git_repository_init_options -> IO (CInt)
foreign import ccall "&git_repository_init_ext" p'git_repository_init_ext
  :: FunPtr (Ptr (Ptr C'git_repository) -> CString -> Ptr C'git_repository_init_options -> IO (CInt))

{-# LINE 70 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_head" c'git_repository_head
  :: Ptr (Ptr C'git_reference) -> Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_head" p'git_repository_head
  :: FunPtr (Ptr (Ptr C'git_reference) -> Ptr C'git_repository -> IO (CInt))

{-# LINE 71 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_head_detached" c'git_repository_head_detached
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_head_detached" p'git_repository_head_detached
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 72 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_head_orphan" c'git_repository_head_orphan
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_head_orphan" p'git_repository_head_orphan
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 73 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_is_empty" c'git_repository_is_empty
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_is_empty" p'git_repository_is_empty
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 74 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_path" c'git_repository_path
  :: Ptr C'git_repository -> IO (CString)
foreign import ccall "&git_repository_path" p'git_repository_path
  :: FunPtr (Ptr C'git_repository -> IO (CString))

{-# LINE 75 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_workdir" c'git_repository_workdir
  :: Ptr C'git_repository -> IO (CString)
foreign import ccall "&git_repository_workdir" p'git_repository_workdir
  :: FunPtr (Ptr C'git_repository -> IO (CString))

{-# LINE 76 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_set_workdir" c'git_repository_set_workdir
  :: Ptr C'git_repository -> CString -> CInt -> IO (CInt)
foreign import ccall "&git_repository_set_workdir" p'git_repository_set_workdir
  :: FunPtr (Ptr C'git_repository -> CString -> CInt -> IO (CInt))

{-# LINE 77 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_is_bare" c'git_repository_is_bare
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_is_bare" p'git_repository_is_bare
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 78 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_config" c'git_repository_config
  :: Ptr (Ptr C'git_config) -> Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_config" p'git_repository_config
  :: FunPtr (Ptr (Ptr C'git_config) -> Ptr C'git_repository -> IO (CInt))

{-# LINE 79 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_set_config" c'git_repository_set_config
  :: Ptr C'git_repository -> Ptr C'git_config -> IO ()
foreign import ccall "&git_repository_set_config" p'git_repository_set_config
  :: FunPtr (Ptr C'git_repository -> Ptr C'git_config -> IO ())

{-# LINE 80 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_odb" c'git_repository_odb
  :: Ptr (Ptr C'git_odb) -> Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_odb" p'git_repository_odb
  :: FunPtr (Ptr (Ptr C'git_odb) -> Ptr C'git_repository -> IO (CInt))

{-# LINE 81 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_set_odb" c'git_repository_set_odb
  :: Ptr C'git_repository -> Ptr C'git_odb -> IO ()
foreign import ccall "&git_repository_set_odb" p'git_repository_set_odb
  :: FunPtr (Ptr C'git_repository -> Ptr C'git_odb -> IO ())

{-# LINE 82 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_refdb" c'git_repository_refdb
  :: Ptr (Ptr C'git_refdb) -> Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_refdb" p'git_repository_refdb
  :: FunPtr (Ptr (Ptr C'git_refdb) -> Ptr C'git_repository -> IO (CInt))

{-# LINE 83 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_set_refdb" c'git_repository_set_refdb
  :: Ptr C'git_repository -> Ptr C'git_refdb -> IO ()
foreign import ccall "&git_repository_set_refdb" p'git_repository_set_refdb
  :: FunPtr (Ptr C'git_repository -> Ptr C'git_refdb -> IO ())

{-# LINE 84 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_index" c'git_repository_index
  :: Ptr (Ptr C'git_index) -> Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_index" p'git_repository_index
  :: FunPtr (Ptr (Ptr C'git_index) -> Ptr C'git_repository -> IO (CInt))

{-# LINE 85 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_set_index" c'git_repository_set_index
  :: Ptr C'git_repository -> Ptr C'git_index -> IO ()
foreign import ccall "&git_repository_set_index" p'git_repository_set_index
  :: FunPtr (Ptr C'git_repository -> Ptr C'git_index -> IO ())

{-# LINE 86 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_message" c'git_repository_message
  :: CString -> CSize -> Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_message" p'git_repository_message
  :: FunPtr (CString -> CSize -> Ptr C'git_repository -> IO (CInt))

{-# LINE 87 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_message_remove" c'git_repository_message_remove
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_message_remove" p'git_repository_message_remove
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 88 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_merge_cleanup" c'git_repository_merge_cleanup
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_merge_cleanup" p'git_repository_merge_cleanup
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 89 "Bindings/Libgit2/Repository.hsc" #-}
{- typedef int (* git_repository_fetchhead_foreach_cb)(const char * ref_name,
                                                    const char * remote_url,
                                                    const git_oid * oid,
                                                    unsigned int is_merge,
                                                    void * payload); -}
type C'git_repository_fetchhead_foreach_cb = FunPtr (CString -> CString -> Ptr (C'git_oid) -> CUInt -> Ptr () -> IO CInt)
foreign import ccall "wrapper" mk'git_repository_fetchhead_foreach_cb
  :: (CString -> CString -> Ptr (C'git_oid) -> CUInt -> Ptr () -> IO CInt) -> IO C'git_repository_fetchhead_foreach_cb
foreign import ccall "dynamic" mK'git_repository_fetchhead_foreach_cb
  :: C'git_repository_fetchhead_foreach_cb -> (CString -> CString -> Ptr (C'git_oid) -> CUInt -> Ptr () -> IO CInt)

{-# LINE 95 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_fetchhead_foreach" c'git_repository_fetchhead_foreach
  :: Ptr C'git_repository -> C'git_repository_fetchhead_foreach_cb -> Ptr () -> IO (CInt)
foreign import ccall "&git_repository_fetchhead_foreach" p'git_repository_fetchhead_foreach
  :: FunPtr (Ptr C'git_repository -> C'git_repository_fetchhead_foreach_cb -> Ptr () -> IO (CInt))

{-# LINE 96 "Bindings/Libgit2/Repository.hsc" #-}
{- typedef int (* git_repository_mergehead_foreach_cb)(const git_oid * oid,
                                                    void * payload); -}
type C'git_repository_mergehead_foreach_cb = FunPtr (Ptr (C'git_oid) -> Ptr () -> IO CInt)
foreign import ccall "wrapper" mk'git_repository_mergehead_foreach_cb
  :: (Ptr (C'git_oid) -> Ptr () -> IO CInt) -> IO C'git_repository_mergehead_foreach_cb
foreign import ccall "dynamic" mK'git_repository_mergehead_foreach_cb
  :: C'git_repository_mergehead_foreach_cb -> (Ptr (C'git_oid) -> Ptr () -> IO CInt)

{-# LINE 99 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_mergehead_foreach" c'git_repository_mergehead_foreach
  :: Ptr C'git_repository -> C'git_repository_mergehead_foreach_cb -> Ptr () -> IO (CInt)
foreign import ccall "&git_repository_mergehead_foreach" p'git_repository_mergehead_foreach
  :: FunPtr (Ptr C'git_repository -> C'git_repository_mergehead_foreach_cb -> Ptr () -> IO (CInt))

{-# LINE 100 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_hashfile" c'git_repository_hashfile
  :: Ptr C'git_oid -> Ptr C'git_repository -> CString -> C'git_otype -> CString -> IO (CInt)
foreign import ccall "&git_repository_hashfile" p'git_repository_hashfile
  :: FunPtr (Ptr C'git_oid -> Ptr C'git_repository -> CString -> C'git_otype -> CString -> IO (CInt))

{-# LINE 101 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_set_head" c'git_repository_set_head
  :: Ptr C'git_repository -> CString -> IO (CInt)
foreign import ccall "&git_repository_set_head" p'git_repository_set_head
  :: FunPtr (Ptr C'git_repository -> CString -> IO (CInt))

{-# LINE 102 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_set_head_detached" c'git_repository_set_head_detached
  :: Ptr C'git_repository -> Ptr C'git_oid -> IO (CInt)
foreign import ccall "&git_repository_set_head_detached" p'git_repository_set_head_detached
  :: FunPtr (Ptr C'git_repository -> Ptr C'git_oid -> IO (CInt))

{-# LINE 103 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_detach_head" c'git_repository_detach_head
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_detach_head" p'git_repository_detach_head
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 104 "Bindings/Libgit2/Repository.hsc" #-}
{- typedef enum {
            GIT_REPOSITORY_STATE_NONE,
            GIT_REPOSITORY_STATE_MERGE,
            GIT_REPOSITORY_STATE_REVERT,
            GIT_REPOSITORY_STATE_CHERRY_PICK,
            GIT_REPOSITORY_STATE_BISECT,
            GIT_REPOSITORY_STATE_REBASE,
            GIT_REPOSITORY_STATE_REBASE_INTERACTIVE,
            GIT_REPOSITORY_STATE_REBASE_MERGE,
            GIT_REPOSITORY_STATE_APPLY_MAILBOX,
            GIT_REPOSITORY_STATE_APPLY_MAILBOX_OR_REBASE
        } git_repository_state_t; -}
type C'git_repository_state_t = CUInt

{-# LINE 117 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_NONE = 0
c'GIT_REPOSITORY_STATE_NONE :: (Num a) => a

{-# LINE 118 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_MERGE = 1
c'GIT_REPOSITORY_STATE_MERGE :: (Num a) => a

{-# LINE 119 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_REVERT = 2
c'GIT_REPOSITORY_STATE_REVERT :: (Num a) => a

{-# LINE 120 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_CHERRY_PICK = 3
c'GIT_REPOSITORY_STATE_CHERRY_PICK :: (Num a) => a

{-# LINE 121 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_BISECT = 4
c'GIT_REPOSITORY_STATE_BISECT :: (Num a) => a

{-# LINE 122 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_REBASE = 5
c'GIT_REPOSITORY_STATE_REBASE :: (Num a) => a

{-# LINE 123 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_REBASE_INTERACTIVE = 6
c'GIT_REPOSITORY_STATE_REBASE_INTERACTIVE :: (Num a) => a

{-# LINE 124 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_REBASE_MERGE = 7
c'GIT_REPOSITORY_STATE_REBASE_MERGE :: (Num a) => a

{-# LINE 125 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_APPLY_MAILBOX = 8
c'GIT_REPOSITORY_STATE_APPLY_MAILBOX :: (Num a) => a

{-# LINE 126 "Bindings/Libgit2/Repository.hsc" #-}
c'GIT_REPOSITORY_STATE_APPLY_MAILBOX_OR_REBASE = 9
c'GIT_REPOSITORY_STATE_APPLY_MAILBOX_OR_REBASE :: (Num a) => a

{-# LINE 127 "Bindings/Libgit2/Repository.hsc" #-}
foreign import ccall "git_repository_state" c'git_repository_state
  :: Ptr C'git_repository -> IO (CInt)
foreign import ccall "&git_repository_state" p'git_repository_state
  :: FunPtr (Ptr C'git_repository -> IO (CInt))

{-# LINE 128 "Bindings/Libgit2/Repository.hsc" #-}