{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents an index object.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Ggit.Objects.Index
    ( 

-- * Exported types
    Index(..)                               ,
    IsIndex                                 ,
    toIndex                                 ,
    noIndex                                 ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveIndexMethod                      ,
#endif


-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    IndexAddMethodInfo                      ,
#endif
    indexAdd                                ,


-- ** addFile #method:addFile#

#if defined(ENABLE_OVERLOADING)
    IndexAddFileMethodInfo                  ,
#endif
    indexAddFile                            ,


-- ** addPath #method:addPath#

#if defined(ENABLE_OVERLOADING)
    IndexAddPathMethodInfo                  ,
#endif
    indexAddPath                            ,


-- ** getEntries #method:getEntries#

#if defined(ENABLE_OVERLOADING)
    IndexGetEntriesMethodInfo               ,
#endif
    indexGetEntries                         ,


-- ** getEntriesResolveUndo #method:getEntriesResolveUndo#

#if defined(ENABLE_OVERLOADING)
    IndexGetEntriesResolveUndoMethodInfo    ,
#endif
    indexGetEntriesResolveUndo              ,


-- ** getOwner #method:getOwner#

#if defined(ENABLE_OVERLOADING)
    IndexGetOwnerMethodInfo                 ,
#endif
    indexGetOwner                           ,


-- ** hasConflicts #method:hasConflicts#

#if defined(ENABLE_OVERLOADING)
    IndexHasConflictsMethodInfo             ,
#endif
    indexHasConflicts                       ,


-- ** open #method:open#

    indexOpen                               ,


-- ** read #method:read#

#if defined(ENABLE_OVERLOADING)
    IndexReadMethodInfo                     ,
#endif
    indexRead                               ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    IndexRemoveMethodInfo                   ,
#endif
    indexRemove                             ,


-- ** write #method:write#

#if defined(ENABLE_OVERLOADING)
    IndexWriteMethodInfo                    ,
#endif
    indexWrite                              ,


-- ** writeTree #method:writeTree#

#if defined(ENABLE_OVERLOADING)
    IndexWriteTreeMethodInfo                ,
#endif
    indexWriteTree                          ,


-- ** writeTreeTo #method:writeTreeTo#

#if defined(ENABLE_OVERLOADING)
    IndexWriteTreeToMethodInfo              ,
#endif
    indexWriteTreeTo                        ,




 -- * Properties
-- ** file #attr:file#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    IndexFilePropertyInfo                   ,
#endif
    constructIndexFile                      ,
    getIndexFile                            ,
#if defined(ENABLE_OVERLOADING)
    indexFile                               ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Ggit.Objects.Native as Ggit.Native
import {-# SOURCE #-} qualified GI.Ggit.Objects.ObjectFactoryBase as Ggit.ObjectFactoryBase
import {-# SOURCE #-} qualified GI.Ggit.Objects.Repository as Ggit.Repository
import {-# SOURCE #-} qualified GI.Ggit.Structs.IndexEntries as Ggit.IndexEntries
import {-# SOURCE #-} qualified GI.Ggit.Structs.IndexEntriesResolveUndo as Ggit.IndexEntriesResolveUndo
import {-# SOURCE #-} qualified GI.Ggit.Structs.IndexEntry as Ggit.IndexEntry
import {-# SOURCE #-} qualified GI.Ggit.Structs.OId as Ggit.OId
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Initable as Gio.Initable

-- | Memory-managed wrapper type.
newtype Index = Index (ManagedPtr Index)
    deriving (Index -> Index -> Bool
(Index -> Index -> Bool) -> (Index -> Index -> Bool) -> Eq Index
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Index -> Index -> Bool
$c/= :: Index -> Index -> Bool
== :: Index -> Index -> Bool
$c== :: Index -> Index -> Bool
Eq)
foreign import ccall "ggit_index_get_type"
    c_ggit_index_get_type :: IO GType

instance GObject Index where
    gobjectType :: IO GType
gobjectType = IO GType
c_ggit_index_get_type
    

-- | Convert 'Index' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Index where
    toGValue :: Index -> IO GValue
toGValue o :: Index
o = do
        GType
gtype <- IO GType
c_ggit_index_get_type
        Index -> (Ptr Index -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Index
o (GType -> (GValue -> Ptr Index -> IO ()) -> Ptr Index -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Index -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Index
fromGValue gv :: GValue
gv = do
        Ptr Index
ptr <- GValue -> IO (Ptr Index)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Index)
        (ManagedPtr Index -> Index) -> Ptr Index -> IO Index
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Index -> Index
Index Ptr Index
ptr
        
    

-- | Type class for types which can be safely cast to `Index`, for instance with `toIndex`.
class (GObject o, O.IsDescendantOf Index o) => IsIndex o
instance (GObject o, O.IsDescendantOf Index o) => IsIndex o

instance O.HasParentTypes Index
type instance O.ParentTypes Index = '[Ggit.Native.Native, Ggit.ObjectFactoryBase.ObjectFactoryBase, GObject.Object.Object, Gio.Initable.Initable]

-- | Cast to `Index`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toIndex :: (MonadIO m, IsIndex o) => o -> m Index
toIndex :: o -> m Index
toIndex = IO Index -> m Index
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Index -> m Index) -> (o -> IO Index) -> o -> m Index
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Index -> Index) -> o -> IO Index
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Index -> Index
Index

-- | A convenience alias for `Nothing` :: `Maybe` `Index`.
noIndex :: Maybe Index
noIndex :: Maybe Index
noIndex = Maybe Index
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveIndexMethod (t :: Symbol) (o :: *) :: * where
    ResolveIndexMethod "add" o = IndexAddMethodInfo
    ResolveIndexMethod "addFile" o = IndexAddFileMethodInfo
    ResolveIndexMethod "addPath" o = IndexAddPathMethodInfo
    ResolveIndexMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveIndexMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveIndexMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveIndexMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveIndexMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveIndexMethod "hasConflicts" o = IndexHasConflictsMethodInfo
    ResolveIndexMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveIndexMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveIndexMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveIndexMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveIndexMethod "read" o = IndexReadMethodInfo
    ResolveIndexMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveIndexMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveIndexMethod "remove" o = IndexRemoveMethodInfo
    ResolveIndexMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveIndexMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveIndexMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveIndexMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveIndexMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveIndexMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveIndexMethod "write" o = IndexWriteMethodInfo
    ResolveIndexMethod "writeTree" o = IndexWriteTreeMethodInfo
    ResolveIndexMethod "writeTreeTo" o = IndexWriteTreeToMethodInfo
    ResolveIndexMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveIndexMethod "getEntries" o = IndexGetEntriesMethodInfo
    ResolveIndexMethod "getEntriesResolveUndo" o = IndexGetEntriesResolveUndoMethodInfo
    ResolveIndexMethod "getOwner" o = IndexGetOwnerMethodInfo
    ResolveIndexMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveIndexMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveIndexMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveIndexMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveIndexMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveIndexMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveIndexMethod t Index, O.MethodInfo info Index p) => OL.IsLabel t (Index -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- VVV Prop "file"
   -- Type: TInterface (Name {namespace = "Gio", name = "File"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' index #file
-- @
getIndexFile :: (MonadIO m, IsIndex o) => o -> m (Maybe Gio.File.File)
getIndexFile :: o -> m (Maybe File)
getIndexFile obj :: o
obj = IO (Maybe File) -> m (Maybe File)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe File) -> m (Maybe File))
-> IO (Maybe File) -> m (Maybe File)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr File -> File) -> IO (Maybe File)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "file" ManagedPtr File -> File
Gio.File.File

-- | Construct a `GValueConstruct` with valid value for the “@file@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructIndexFile :: (IsIndex o, Gio.File.IsFile a) => a -> IO (GValueConstruct o)
constructIndexFile :: a -> IO (GValueConstruct o)
constructIndexFile val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "file" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

#if defined(ENABLE_OVERLOADING)
data IndexFilePropertyInfo
instance AttrInfo IndexFilePropertyInfo where
    type AttrAllowedOps IndexFilePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint IndexFilePropertyInfo = IsIndex
    type AttrSetTypeConstraint IndexFilePropertyInfo = Gio.File.IsFile
    type AttrTransferTypeConstraint IndexFilePropertyInfo = Gio.File.IsFile
    type AttrTransferType IndexFilePropertyInfo = Gio.File.File
    type AttrGetType IndexFilePropertyInfo = (Maybe Gio.File.File)
    type AttrLabel IndexFilePropertyInfo = "file"
    type AttrOrigin IndexFilePropertyInfo = Index
    attrGet = getIndexFile
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.File.File v
    attrConstruct = constructIndexFile
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Index
type instance O.AttributeList Index = IndexAttributeList
type IndexAttributeList = ('[ '("file", IndexFilePropertyInfo), '("native", Ggit.Native.NativeNativePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
indexFile :: AttrLabelProxy "file"
indexFile = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Index = IndexSignalList
type IndexSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Index::add
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "IndexEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndexEntry." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_add" ggit_index_add :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr Ggit.IndexEntry.IndexEntry ->       -- entry : TInterface (Name {namespace = "Ggit", name = "IndexEntry"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Add a file to the index.
indexAdd ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> Ggit.IndexEntry.IndexEntry
    -- ^ /@entry@/: a t'GI.Ggit.Structs.IndexEntry.IndexEntry'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
indexAdd :: a -> IndexEntry -> m ()
indexAdd idx :: a
idx entry :: IndexEntry
entry = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    Ptr IndexEntry
entry' <- IndexEntry -> IO (Ptr IndexEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IndexEntry
entry
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Index -> Ptr IndexEntry -> Ptr (Ptr GError) -> IO CInt
ggit_index_add Ptr Index
idx' Ptr IndexEntry
entry'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        IndexEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IndexEntry
entry
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data IndexAddMethodInfo
instance (signature ~ (Ggit.IndexEntry.IndexEntry -> m ()), MonadIO m, IsIndex a) => O.MethodInfo IndexAddMethodInfo a signature where
    overloadedMethod = indexAdd

#endif

-- method Index::add_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "file to add." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_add_file" ggit_index_add_file :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Add a file to the index. The specified file must be in the working directory
-- and must exist and be readable.
indexAddFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a, Gio.File.IsFile b) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> b
    -- ^ /@file@/: file to add.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
indexAddFile :: a -> b -> m ()
indexAddFile idx :: a
idx file :: b
file = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    Ptr File
file' <- b -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
file
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Index -> Ptr File -> Ptr (Ptr GError) -> IO CInt
ggit_index_add_file Ptr Index
idx' Ptr File
file'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
file
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data IndexAddFileMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsIndex a, Gio.File.IsFile b) => O.MethodInfo IndexAddFileMethodInfo a signature where
    overloadedMethod = indexAddFile

#endif

-- method Index::add_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path to the file to add."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_add_path" ggit_index_add_path :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    CString ->                              -- path : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Add a file to the index by path. You can specify both relative paths
-- (to the working directory) and absolute paths. Absolute paths however must
-- reside in the working directory. The specified path must exist and must be
-- readable.
indexAddPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> T.Text
    -- ^ /@path@/: path to the file to add.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
indexAddPath :: a -> Text -> m ()
indexAddPath idx :: a
idx path :: Text
path = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    CString
path' <- Text -> IO CString
textToCString Text
path
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Index -> CString -> Ptr (Ptr GError) -> IO CInt
ggit_index_add_path Ptr Index
idx' CString
path'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
     )

#if defined(ENABLE_OVERLOADING)
data IndexAddPathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsIndex a) => O.MethodInfo IndexAddPathMethodInfo a signature where
    overloadedMethod = indexAddPath

#endif

-- method Index::get_entries
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Ggit" , name = "IndexEntries" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_index_get_entries" ggit_index_get_entries :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    IO (Ptr Ggit.IndexEntries.IndexEntries)

-- | Get the index entries enumerator.
indexGetEntries ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> m (Maybe Ggit.IndexEntries.IndexEntries)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.IndexEntries.IndexEntries' or 'P.Nothing'.
indexGetEntries :: a -> m (Maybe IndexEntries)
indexGetEntries idx :: a
idx = IO (Maybe IndexEntries) -> m (Maybe IndexEntries)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IndexEntries) -> m (Maybe IndexEntries))
-> IO (Maybe IndexEntries) -> m (Maybe IndexEntries)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    Ptr IndexEntries
result <- Ptr Index -> IO (Ptr IndexEntries)
ggit_index_get_entries Ptr Index
idx'
    Maybe IndexEntries
maybeResult <- Ptr IndexEntries
-> (Ptr IndexEntries -> IO IndexEntries) -> IO (Maybe IndexEntries)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IndexEntries
result ((Ptr IndexEntries -> IO IndexEntries) -> IO (Maybe IndexEntries))
-> (Ptr IndexEntries -> IO IndexEntries) -> IO (Maybe IndexEntries)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IndexEntries
result' -> do
        IndexEntries
result'' <- ((ManagedPtr IndexEntries -> IndexEntries)
-> Ptr IndexEntries -> IO IndexEntries
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr IndexEntries -> IndexEntries
Ggit.IndexEntries.IndexEntries) Ptr IndexEntries
result'
        IndexEntries -> IO IndexEntries
forall (m :: * -> *) a. Monad m => a -> m a
return IndexEntries
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
    Maybe IndexEntries -> IO (Maybe IndexEntries)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IndexEntries
maybeResult

#if defined(ENABLE_OVERLOADING)
data IndexGetEntriesMethodInfo
instance (signature ~ (m (Maybe Ggit.IndexEntries.IndexEntries)), MonadIO m, IsIndex a) => O.MethodInfo IndexGetEntriesMethodInfo a signature where
    overloadedMethod = indexGetEntries

#endif

-- method Index::get_entries_resolve_undo
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Ggit" , name = "IndexEntriesResolveUndo" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_index_get_entries_resolve_undo" ggit_index_get_entries_resolve_undo :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    IO (Ptr Ggit.IndexEntriesResolveUndo.IndexEntriesResolveUndo)

-- | Get the resolve undo entries enumerator.
indexGetEntriesResolveUndo ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> m (Maybe Ggit.IndexEntriesResolveUndo.IndexEntriesResolveUndo)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.IndexEntriesResolveUndo.IndexEntriesResolveUndo' or 'P.Nothing'.
indexGetEntriesResolveUndo :: a -> m (Maybe IndexEntriesResolveUndo)
indexGetEntriesResolveUndo idx :: a
idx = IO (Maybe IndexEntriesResolveUndo)
-> m (Maybe IndexEntriesResolveUndo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IndexEntriesResolveUndo)
 -> m (Maybe IndexEntriesResolveUndo))
-> IO (Maybe IndexEntriesResolveUndo)
-> m (Maybe IndexEntriesResolveUndo)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    Ptr IndexEntriesResolveUndo
result <- Ptr Index -> IO (Ptr IndexEntriesResolveUndo)
ggit_index_get_entries_resolve_undo Ptr Index
idx'
    Maybe IndexEntriesResolveUndo
maybeResult <- Ptr IndexEntriesResolveUndo
-> (Ptr IndexEntriesResolveUndo -> IO IndexEntriesResolveUndo)
-> IO (Maybe IndexEntriesResolveUndo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IndexEntriesResolveUndo
result ((Ptr IndexEntriesResolveUndo -> IO IndexEntriesResolveUndo)
 -> IO (Maybe IndexEntriesResolveUndo))
-> (Ptr IndexEntriesResolveUndo -> IO IndexEntriesResolveUndo)
-> IO (Maybe IndexEntriesResolveUndo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IndexEntriesResolveUndo
result' -> do
        IndexEntriesResolveUndo
result'' <- ((ManagedPtr IndexEntriesResolveUndo -> IndexEntriesResolveUndo)
-> Ptr IndexEntriesResolveUndo -> IO IndexEntriesResolveUndo
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr IndexEntriesResolveUndo -> IndexEntriesResolveUndo
Ggit.IndexEntriesResolveUndo.IndexEntriesResolveUndo) Ptr IndexEntriesResolveUndo
result'
        IndexEntriesResolveUndo -> IO IndexEntriesResolveUndo
forall (m :: * -> *) a. Monad m => a -> m a
return IndexEntriesResolveUndo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
    Maybe IndexEntriesResolveUndo -> IO (Maybe IndexEntriesResolveUndo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IndexEntriesResolveUndo
maybeResult

#if defined(ENABLE_OVERLOADING)
data IndexGetEntriesResolveUndoMethodInfo
instance (signature ~ (m (Maybe Ggit.IndexEntriesResolveUndo.IndexEntriesResolveUndo)), MonadIO m, IsIndex a) => O.MethodInfo IndexGetEntriesResolveUndoMethodInfo a signature where
    overloadedMethod = indexGetEntriesResolveUndo

#endif

-- method Index::get_owner
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Repository" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_index_get_owner" ggit_index_get_owner :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    IO (Ptr Ggit.Repository.Repository)

-- | Get the t'GI.Ggit.Objects.Repository.Repository' that owns the index.
indexGetOwner ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> m (Maybe Ggit.Repository.Repository)
    -- ^ __Returns:__ the t'GI.Ggit.Objects.Repository.Repository' that owns this index or 'P.Nothing'.
indexGetOwner :: a -> m (Maybe Repository)
indexGetOwner idx :: a
idx = IO (Maybe Repository) -> m (Maybe Repository)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Repository) -> m (Maybe Repository))
-> IO (Maybe Repository) -> m (Maybe Repository)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    Ptr Repository
result <- Ptr Index -> IO (Ptr Repository)
ggit_index_get_owner Ptr Index
idx'
    Maybe Repository
maybeResult <- Ptr Repository
-> (Ptr Repository -> IO Repository) -> IO (Maybe Repository)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Repository
result ((Ptr Repository -> IO Repository) -> IO (Maybe Repository))
-> (Ptr Repository -> IO Repository) -> IO (Maybe Repository)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Repository
result' -> do
        Repository
result'' <- ((ManagedPtr Repository -> Repository)
-> Ptr Repository -> IO Repository
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Repository -> Repository
Ggit.Repository.Repository) Ptr Repository
result'
        Repository -> IO Repository
forall (m :: * -> *) a. Monad m => a -> m a
return Repository
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
    Maybe Repository -> IO (Maybe Repository)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Repository
maybeResult

#if defined(ENABLE_OVERLOADING)
data IndexGetOwnerMethodInfo
instance (signature ~ (m (Maybe Ggit.Repository.Repository)), MonadIO m, IsIndex a) => O.MethodInfo IndexGetOwnerMethodInfo a signature where
    overloadedMethod = indexGetOwner

#endif

-- method Index::has_conflicts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "ggit_index_has_conflicts" ggit_index_has_conflicts :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    IO CInt

-- | Get whether the index has any conflicts.
indexHasConflicts ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the index has any conflicts, 'P.False' otherwise.
indexHasConflicts :: a -> m Bool
indexHasConflicts idx :: a
idx = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    CInt
result <- Ptr Index -> IO CInt
ggit_index_has_conflicts Ptr Index
idx'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data IndexHasConflictsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsIndex a) => O.MethodInfo IndexHasConflictsMethodInfo a signature where
    overloadedMethod = indexHasConflicts

#endif

-- method Index::read
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "force"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "force read even if there are in-memory changes."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_read" ggit_index_read :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    CInt ->                                 -- force : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Update the contents of an existing index object in memory by reading from
-- the hard disk.
-- 
-- If /@force@/ is true, this performs a \"hard\" read that discards in-memory
-- changes and always reloads the on-disk index data. If there is no on-disk
-- version, the index will be cleared.
-- 
-- If /@force@/ is false, this does a \"soft\" read that reloads the index data from
-- disk only if it has changed since the last time it was loaded. Purely
-- in-memory index data will be untouched. Be aware: if there are changes on
-- disk, unwritten in-memory changes are discarded.
indexRead ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> Bool
    -- ^ /@force@/: force read even if there are in-memory changes.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
indexRead :: a -> Bool -> m ()
indexRead idx :: a
idx force :: Bool
force = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    let force' :: CInt
force' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
force
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Index -> CInt -> Ptr (Ptr GError) -> IO CInt
ggit_index_read Ptr Index
idx' CInt
force'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data IndexReadMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsIndex a) => O.MethodInfo IndexReadMethodInfo a signature where
    overloadedMethod = indexRead

#endif

-- method Index::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file to search."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stage"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the stage to search."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_remove" ggit_index_remove :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    Int32 ->                                -- stage : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Remove a file from the index (specified by position).
indexRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a, Gio.File.IsFile b) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> b
    -- ^ /@file@/: the file to search.
    -> Int32
    -- ^ /@stage@/: the stage to search.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
indexRemove :: a -> b -> Int32 -> m ()
indexRemove idx :: a
idx file :: b
file stage :: Int32
stage = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    Ptr File
file' <- b -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
file
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Index -> Ptr File -> Int32 -> Ptr (Ptr GError) -> IO CInt
ggit_index_remove Ptr Index
idx' Ptr File
file' Int32
stage
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
file
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data IndexRemoveMethodInfo
instance (signature ~ (b -> Int32 -> m ()), MonadIO m, IsIndex a, Gio.File.IsFile b) => O.MethodInfo IndexRemoveMethodInfo a signature where
    overloadedMethod = indexRemove

#endif

-- method Index::write
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_write" ggit_index_write :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Write an existing index object from memory back to disk using an atomic file
-- lock.
indexWrite ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
indexWrite :: a -> m ()
indexWrite idx :: a
idx = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Index -> Ptr (Ptr GError) -> IO CInt
ggit_index_write Ptr Index
idx'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data IndexWriteMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIndex a) => O.MethodInfo IndexWriteMethodInfo a signature where
    overloadedMethod = indexWrite

#endif

-- method Index::write_tree
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "OId" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_write_tree" ggit_index_write_tree :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Ggit.OId.OId)

-- | Write a new tree object to disk containing a representation of the current
-- state of the index. The index must be associated to an existing repository
-- and must not contain any files in conflict. You can use the resulting tree
-- to for instance create a commit.
indexWriteTree ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> m (Maybe Ggit.OId.OId)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.OId.OId' or 'P.Nothing' in case of an error. /(Can throw 'Data.GI.Base.GError.GError')/
indexWriteTree :: a -> m (Maybe OId)
indexWriteTree idx :: a
idx = IO (Maybe OId) -> m (Maybe OId)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe OId) -> m (Maybe OId))
-> IO (Maybe OId) -> m (Maybe OId)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    IO (Maybe OId) -> IO () -> IO (Maybe OId)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr OId
result <- (Ptr (Ptr GError) -> IO (Ptr OId)) -> IO (Ptr OId)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr OId)) -> IO (Ptr OId))
-> (Ptr (Ptr GError) -> IO (Ptr OId)) -> IO (Ptr OId)
forall a b. (a -> b) -> a -> b
$ Ptr Index -> Ptr (Ptr GError) -> IO (Ptr OId)
ggit_index_write_tree Ptr Index
idx'
        Maybe OId
maybeResult <- Ptr OId -> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr OId
result ((Ptr OId -> IO OId) -> IO (Maybe OId))
-> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr OId
result' -> do
            OId
result'' <- ((ManagedPtr OId -> OId) -> Ptr OId -> IO OId
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr OId -> OId
Ggit.OId.OId) Ptr OId
result'
            OId -> IO OId
forall (m :: * -> *) a. Monad m => a -> m a
return OId
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        Maybe OId -> IO (Maybe OId)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OId
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data IndexWriteTreeMethodInfo
instance (signature ~ (m (Maybe Ggit.OId.OId)), MonadIO m, IsIndex a) => O.MethodInfo IndexWriteTreeMethodInfo a signature where
    overloadedMethod = indexWriteTree

#endif

-- method Index::write_tree_to
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "idx"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "repository"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "Repository" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitRepository." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "OId" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_write_tree_to" ggit_index_write_tree_to :: 
    Ptr Index ->                            -- idx : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr Ggit.Repository.Repository ->       -- repository : TInterface (Name {namespace = "Ggit", name = "Repository"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Ggit.OId.OId)

-- | Write a new tree object to /@repository@/ containing a representation of the current
-- state of the index. The index must not contain any files in conflict. You can use
-- the resulting tree to for instance create a commit.
indexWriteTreeTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsIndex a, Ggit.Repository.IsRepository b) =>
    a
    -- ^ /@idx@/: a t'GI.Ggit.Objects.Index.Index'.
    -> b
    -- ^ /@repository@/: a t'GI.Ggit.Objects.Repository.Repository'.
    -> m (Maybe Ggit.OId.OId)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.OId.OId' or 'P.Nothing' in case of an error. /(Can throw 'Data.GI.Base.GError.GError')/
indexWriteTreeTo :: a -> b -> m (Maybe OId)
indexWriteTreeTo idx :: a
idx repository :: b
repository = IO (Maybe OId) -> m (Maybe OId)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe OId) -> m (Maybe OId))
-> IO (Maybe OId) -> m (Maybe OId)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Index
idx' <- a -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
idx
    Ptr Repository
repository' <- b -> IO (Ptr Repository)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
repository
    IO (Maybe OId) -> IO () -> IO (Maybe OId)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr OId
result <- (Ptr (Ptr GError) -> IO (Ptr OId)) -> IO (Ptr OId)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr OId)) -> IO (Ptr OId))
-> (Ptr (Ptr GError) -> IO (Ptr OId)) -> IO (Ptr OId)
forall a b. (a -> b) -> a -> b
$ Ptr Index -> Ptr Repository -> Ptr (Ptr GError) -> IO (Ptr OId)
ggit_index_write_tree_to Ptr Index
idx' Ptr Repository
repository'
        Maybe OId
maybeResult <- Ptr OId -> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr OId
result ((Ptr OId -> IO OId) -> IO (Maybe OId))
-> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr OId
result' -> do
            OId
result'' <- ((ManagedPtr OId -> OId) -> Ptr OId -> IO OId
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr OId -> OId
Ggit.OId.OId) Ptr OId
result'
            OId -> IO OId
forall (m :: * -> *) a. Monad m => a -> m a
return OId
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
idx
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
repository
        Maybe OId -> IO (Maybe OId)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OId
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data IndexWriteTreeToMethodInfo
instance (signature ~ (b -> m (Maybe Ggit.OId.OId)), MonadIO m, IsIndex a, Ggit.Repository.IsRepository b) => O.MethodInfo IndexWriteTreeToMethodInfo a signature where
    overloadedMethod = indexWriteTreeTo

#endif

-- method Index::open
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFile." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Index" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_index_open" ggit_index_open :: 
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Index)

-- | Create a new bare Git index object as a memory representation of the Git
-- index file in /@file@/, without a repository to back it.
indexOpen ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a) =>
    a
    -- ^ /@file@/: a t'GI.Gio.Interfaces.File.File'.
    -> m (Maybe Index)
    -- ^ __Returns:__ a t'GI.Ggit.Objects.Index.Index' or 'P.Nothing' if an error occurred. /(Can throw 'Data.GI.Base.GError.GError')/
indexOpen :: a -> m (Maybe Index)
indexOpen file :: a
file = IO (Maybe Index) -> m (Maybe Index)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Index) -> m (Maybe Index))
-> IO (Maybe Index) -> m (Maybe Index)
forall a b. (a -> b) -> a -> b
$ do
    Ptr File
file' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
file
    IO (Maybe Index) -> IO () -> IO (Maybe Index)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Index
result <- (Ptr (Ptr GError) -> IO (Ptr Index)) -> IO (Ptr Index)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Index)) -> IO (Ptr Index))
-> (Ptr (Ptr GError) -> IO (Ptr Index)) -> IO (Ptr Index)
forall a b. (a -> b) -> a -> b
$ Ptr File -> Ptr (Ptr GError) -> IO (Ptr Index)
ggit_index_open Ptr File
file'
        Maybe Index
maybeResult <- Ptr Index -> (Ptr Index -> IO Index) -> IO (Maybe Index)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Index
result ((Ptr Index -> IO Index) -> IO (Maybe Index))
-> (Ptr Index -> IO Index) -> IO (Maybe Index)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Index
result' -> do
            Index
result'' <- ((ManagedPtr Index -> Index) -> Ptr Index -> IO Index
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Index -> Index
Index) Ptr Index
result'
            Index -> IO Index
forall (m :: * -> *) a. Monad m => a -> m a
return Index
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
file
        Maybe Index -> IO (Maybe Index)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Index
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif