{-# LANGUAGE TypeApplications #-}


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

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

module GI.Ggit.Objects.Tree
    ( 

-- * Exported types
    Tree(..)                                ,
    IsTree                                  ,
    toTree                                  ,
    noTree                                  ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTreeMethod                       ,
#endif


-- ** get #method:get#

#if defined(ENABLE_OVERLOADING)
    TreeGetMethodInfo                       ,
#endif
    treeGet                                 ,


-- ** getByName #method:getByName#

#if defined(ENABLE_OVERLOADING)
    TreeGetByNameMethodInfo                 ,
#endif
    treeGetByName                           ,


-- ** getByPath #method:getByPath#

#if defined(ENABLE_OVERLOADING)
    TreeGetByPathMethodInfo                 ,
#endif
    treeGetByPath                           ,


-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    TreeGetIdMethodInfo                     ,
#endif
    treeGetId                               ,


-- ** size #method:size#

#if defined(ENABLE_OVERLOADING)
    TreeSizeMethodInfo                      ,
#endif
    treeSize                                ,


-- ** walk #method:walk#

#if defined(ENABLE_OVERLOADING)
    TreeWalkMethodInfo                      ,
#endif
    treeWalk                                ,




    ) 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 qualified GI.Ggit.Callbacks as Ggit.Callbacks
import {-# SOURCE #-} qualified GI.Ggit.Enums as Ggit.Enums
import {-# SOURCE #-} qualified GI.Ggit.Objects.Native as Ggit.Native
import {-# SOURCE #-} qualified GI.Ggit.Objects.Object as Ggit.Object
import {-# SOURCE #-} qualified GI.Ggit.Objects.ObjectFactoryBase as Ggit.ObjectFactoryBase
import {-# SOURCE #-} qualified GI.Ggit.Structs.OId as Ggit.OId
import {-# SOURCE #-} qualified GI.Ggit.Structs.TreeEntry as Ggit.TreeEntry

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

instance GObject Tree where
    gobjectType :: IO GType
gobjectType = IO GType
c_ggit_tree_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `Tree`.
noTree :: Maybe Tree
noTree :: Maybe Tree
noTree = Maybe Tree
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveTreeMethod (t :: Symbol) (o :: *) :: * where
    ResolveTreeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTreeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTreeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTreeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTreeMethod "get" o = TreeGetMethodInfo
    ResolveTreeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTreeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTreeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTreeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTreeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTreeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTreeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTreeMethod "size" o = TreeSizeMethodInfo
    ResolveTreeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTreeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTreeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTreeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTreeMethod "walk" o = TreeWalkMethodInfo
    ResolveTreeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTreeMethod "getByName" o = TreeGetByNameMethodInfo
    ResolveTreeMethod "getByPath" o = TreeGetByPathMethodInfo
    ResolveTreeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTreeMethod "getId" o = TreeGetIdMethodInfo
    ResolveTreeMethod "getOwner" o = Ggit.Object.ObjectGetOwnerMethodInfo
    ResolveTreeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTreeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTreeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTreeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTreeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTreeMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method Tree::get
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of the entry."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "TreeEntry" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_tree_get" ggit_tree_get :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    Word32 ->                               -- i : TBasicType TUInt
    IO (Ptr Ggit.TreeEntry.TreeEntry)

-- | Get a tree entry by index.
treeGet ::
    (B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
    a
    -- ^ /@tree@/: a t'GI.Ggit.Objects.Tree.Tree'.
    -> Word32
    -- ^ /@i@/: the index of the entry.
    -> m (Maybe Ggit.TreeEntry.TreeEntry)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.TreeEntry.TreeEntry' or 'P.Nothing'.
treeGet :: a -> Word32 -> m (Maybe TreeEntry)
treeGet tree :: a
tree i :: Word32
i = IO (Maybe TreeEntry) -> m (Maybe TreeEntry)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeEntry) -> m (Maybe TreeEntry))
-> IO (Maybe TreeEntry) -> m (Maybe TreeEntry)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tree
    Ptr TreeEntry
result <- Ptr Tree -> Word32 -> IO (Ptr TreeEntry)
ggit_tree_get Ptr Tree
tree' Word32
i
    Maybe TreeEntry
maybeResult <- Ptr TreeEntry
-> (Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeEntry
result ((Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry))
-> (Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr TreeEntry
result' -> do
        TreeEntry
result'' <- ((ManagedPtr TreeEntry -> TreeEntry)
-> Ptr TreeEntry -> IO TreeEntry
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeEntry -> TreeEntry
Ggit.TreeEntry.TreeEntry) Ptr TreeEntry
result'
        TreeEntry -> IO TreeEntry
forall (m :: * -> *) a. Monad m => a -> m a
return TreeEntry
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tree
    Maybe TreeEntry -> IO (Maybe TreeEntry)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeEntry
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeGetMethodInfo
instance (signature ~ (Word32 -> m (Maybe Ggit.TreeEntry.TreeEntry)), MonadIO m, IsTree a) => O.MethodInfo TreeGetMethodInfo a signature where
    overloadedMethod = treeGet

#endif

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

foreign import ccall "ggit_tree_get_by_name" ggit_tree_get_by_name :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Ggit.TreeEntry.TreeEntry)

-- | Get a tree entry by name.
treeGetByName ::
    (B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
    a
    -- ^ /@tree@/: a t'GI.Ggit.Objects.Tree.Tree'.
    -> T.Text
    -- ^ /@name@/: a filename.
    -> m (Maybe Ggit.TreeEntry.TreeEntry)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.TreeEntry.TreeEntry' or 'P.Nothing'.
treeGetByName :: a -> Text -> m (Maybe TreeEntry)
treeGetByName tree :: a
tree name :: Text
name = IO (Maybe TreeEntry) -> m (Maybe TreeEntry)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeEntry) -> m (Maybe TreeEntry))
-> IO (Maybe TreeEntry) -> m (Maybe TreeEntry)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tree
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr TreeEntry
result <- Ptr Tree -> CString -> IO (Ptr TreeEntry)
ggit_tree_get_by_name Ptr Tree
tree' CString
name'
    Maybe TreeEntry
maybeResult <- Ptr TreeEntry
-> (Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeEntry
result ((Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry))
-> (Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr TreeEntry
result' -> do
        TreeEntry
result'' <- ((ManagedPtr TreeEntry -> TreeEntry)
-> Ptr TreeEntry -> IO TreeEntry
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeEntry -> TreeEntry
Ggit.TreeEntry.TreeEntry) Ptr TreeEntry
result'
        TreeEntry -> IO TreeEntry
forall (m :: * -> *) a. Monad m => a -> m a
return TreeEntry
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tree
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Maybe TreeEntry -> IO (Maybe TreeEntry)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeEntry
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeGetByNameMethodInfo
instance (signature ~ (T.Text -> m (Maybe Ggit.TreeEntry.TreeEntry)), MonadIO m, IsTree a) => O.MethodInfo TreeGetByNameMethodInfo a signature where
    overloadedMethod = treeGetByName

#endif

-- method Tree::get_by_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree." , 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 "a path." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "TreeEntry" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_tree_get_by_path" ggit_tree_get_by_path :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    CString ->                              -- path : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Ggit.TreeEntry.TreeEntry)

-- | Retrieves a tree entry contained in a tree or in any of its subtrees,
-- given its relative path.
treeGetByPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
    a
    -- ^ /@tree@/: a t'GI.Ggit.Objects.Tree.Tree'.
    -> T.Text
    -- ^ /@path@/: a path.
    -> m (Maybe Ggit.TreeEntry.TreeEntry)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.TreeEntry.TreeEntry' or 'P.Nothing'. /(Can throw 'Data.GI.Base.GError.GError')/
treeGetByPath :: a -> Text -> m (Maybe TreeEntry)
treeGetByPath tree :: a
tree path :: Text
path = IO (Maybe TreeEntry) -> m (Maybe TreeEntry)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeEntry) -> m (Maybe TreeEntry))
-> IO (Maybe TreeEntry) -> m (Maybe TreeEntry)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tree
    CString
path' <- Text -> IO CString
textToCString Text
path
    IO (Maybe TreeEntry) -> IO () -> IO (Maybe TreeEntry)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr TreeEntry
result <- (Ptr (Ptr GError) -> IO (Ptr TreeEntry)) -> IO (Ptr TreeEntry)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TreeEntry)) -> IO (Ptr TreeEntry))
-> (Ptr (Ptr GError) -> IO (Ptr TreeEntry)) -> IO (Ptr TreeEntry)
forall a b. (a -> b) -> a -> b
$ Ptr Tree -> CString -> Ptr (Ptr GError) -> IO (Ptr TreeEntry)
ggit_tree_get_by_path Ptr Tree
tree' CString
path'
        Maybe TreeEntry
maybeResult <- Ptr TreeEntry
-> (Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeEntry
result ((Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry))
-> (Ptr TreeEntry -> IO TreeEntry) -> IO (Maybe TreeEntry)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr TreeEntry
result' -> do
            TreeEntry
result'' <- ((ManagedPtr TreeEntry -> TreeEntry)
-> Ptr TreeEntry -> IO TreeEntry
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeEntry -> TreeEntry
Ggit.TreeEntry.TreeEntry) Ptr TreeEntry
result'
            TreeEntry -> IO TreeEntry
forall (m :: * -> *) a. Monad m => a -> m a
return TreeEntry
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tree
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        Maybe TreeEntry -> IO (Maybe TreeEntry)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeEntry
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
     )

#if defined(ENABLE_OVERLOADING)
data TreeGetByPathMethodInfo
instance (signature ~ (T.Text -> m (Maybe Ggit.TreeEntry.TreeEntry)), MonadIO m, IsTree a) => O.MethodInfo TreeGetByPathMethodInfo a signature where
    overloadedMethod = treeGetByPath

#endif

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

foreign import ccall "ggit_tree_get_id" ggit_tree_get_id :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    IO (Ptr Ggit.OId.OId)

-- | Get the t'GI.Ggit.Structs.OId.OId' of the tree.
treeGetId ::
    (B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
    a
    -- ^ /@tree@/: a t'GI.Ggit.Objects.Tree.Tree'.
    -> m (Maybe Ggit.OId.OId)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.OId.OId' or 'P.Nothing'.
treeGetId :: a -> m (Maybe OId)
treeGetId tree :: a
tree = 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 Tree
tree' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tree
    Ptr OId
result <- Ptr Tree -> IO (Ptr OId)
ggit_tree_get_id Ptr Tree
tree'
    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
tree
    Maybe OId -> IO (Maybe OId)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OId
maybeResult

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

#endif

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

foreign import ccall "ggit_tree_size" ggit_tree_size :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    IO Word32

-- | Get the number of entries in the tree.
treeSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
    a
    -- ^ /@tree@/: a t'GI.Ggit.Objects.Tree.Tree'.
    -> m Word32
    -- ^ __Returns:__ the number of entries in the tree.
treeSize :: a -> m Word32
treeSize tree :: a
tree = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Tree
tree' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tree
    Word32
result <- Ptr Tree -> IO Word32
ggit_tree_size Ptr Tree
tree'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tree
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data TreeSizeMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsTree a) => O.MethodInfo TreeSizeMethodInfo a signature where
    overloadedMethod = treeSize

#endif

-- method Tree::walk
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "TreeWalkMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the walking order." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "TreeWalkCallback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the callback to call for each entry."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data for the callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "ggit_tree_walk" ggit_tree_walk :: 
    Ptr Tree ->                             -- tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    CUInt ->                                -- mode : TInterface (Name {namespace = "Ggit", name = "TreeWalkMode"})
    FunPtr Ggit.Callbacks.C_TreeWalkCallback -> -- callback : TInterface (Name {namespace = "Ggit", name = "TreeWalkCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    Ptr (Ptr GError) ->                     -- error
    IO ()

-- | Walk all the entries of a tree object recursively (resolving and walking
-- subtrees of the tree as needed). The /@error@/ will be set to the error returned
-- by /@callback@/ (if any).
treeWalk ::
    (B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
    a
    -- ^ /@tree@/: a t'GI.Ggit.Objects.Tree.Tree'.
    -> Ggit.Enums.TreeWalkMode
    -- ^ /@mode@/: the walking order.
    -> Ggit.Callbacks.TreeWalkCallback
    -- ^ /@callback@/: the callback to call for each entry.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
treeWalk :: a -> TreeWalkMode -> TreeWalkCallback -> m ()
treeWalk tree :: a
tree mode :: TreeWalkMode
mode callback :: TreeWalkCallback
callback = 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 Tree
tree' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tree
    let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TreeWalkMode -> Int) -> TreeWalkMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TreeWalkMode -> Int
forall a. Enum a => a -> Int
fromEnum) TreeWalkMode
mode
    FunPtr C_TreeWalkCallback
callback' <- C_TreeWalkCallback -> IO (FunPtr C_TreeWalkCallback)
Ggit.Callbacks.mk_TreeWalkCallback (Maybe (Ptr (FunPtr C_TreeWalkCallback))
-> TreeWalkCallback_WithClosures -> C_TreeWalkCallback
Ggit.Callbacks.wrap_TreeWalkCallback Maybe (Ptr (FunPtr C_TreeWalkCallback))
forall a. Maybe a
Nothing (TreeWalkCallback -> TreeWalkCallback_WithClosures
Ggit.Callbacks.drop_closures_TreeWalkCallback TreeWalkCallback
callback))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Tree
-> CUInt
-> FunPtr C_TreeWalkCallback
-> Ptr ()
-> Ptr (Ptr GError)
-> IO ()
ggit_tree_walk Ptr Tree
tree' CUInt
mode' FunPtr C_TreeWalkCallback
callback' Ptr ()
forall a. Ptr a
userData
        Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_TreeWalkCallback -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_TreeWalkCallback
callback'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tree
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_TreeWalkCallback -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_TreeWalkCallback
callback'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data TreeWalkMethodInfo
instance (signature ~ (Ggit.Enums.TreeWalkMode -> Ggit.Callbacks.TreeWalkCallback -> m ()), MonadIO m, IsTree a) => O.MethodInfo TreeWalkMethodInfo a signature where
    overloadedMethod = treeWalk

#endif