{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents an annotated commit object.

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

module GI.Ggit.Structs.AnnotatedCommit
    ( 

-- * Exported types
    AnnotatedCommit(..)                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [ref]("GI.Ggit.Structs.AnnotatedCommit#g:method:ref"), [unref]("GI.Ggit.Structs.AnnotatedCommit#g:method:unref").
-- 
-- ==== Getters
-- [getId]("GI.Ggit.Structs.AnnotatedCommit#g:method:getId").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveAnnotatedCommitMethod            ,
#endif

-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    AnnotatedCommitGetIdMethodInfo          ,
#endif
    annotatedCommitGetId                    ,


-- ** newFromRef #method:newFromRef#

    annotatedCommitNewFromRef               ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    AnnotatedCommitRefMethodInfo            ,
#endif
    annotatedCommitRef                      ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    AnnotatedCommitUnrefMethodInfo          ,
#endif
    annotatedCommitUnref                    ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
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 GHC.Records as R

import {-# SOURCE #-} qualified GI.Ggit.Objects.Ref as Ggit.Ref
import {-# SOURCE #-} qualified GI.Ggit.Objects.Repository as Ggit.Repository
import {-# SOURCE #-} qualified GI.Ggit.Structs.OId as Ggit.OId

-- | Memory-managed wrapper type.
newtype AnnotatedCommit = AnnotatedCommit (SP.ManagedPtr AnnotatedCommit)
    deriving (AnnotatedCommit -> AnnotatedCommit -> Bool
(AnnotatedCommit -> AnnotatedCommit -> Bool)
-> (AnnotatedCommit -> AnnotatedCommit -> Bool)
-> Eq AnnotatedCommit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotatedCommit -> AnnotatedCommit -> Bool
== :: AnnotatedCommit -> AnnotatedCommit -> Bool
$c/= :: AnnotatedCommit -> AnnotatedCommit -> Bool
/= :: AnnotatedCommit -> AnnotatedCommit -> Bool
Eq)

instance SP.ManagedPtrNewtype AnnotatedCommit where
    toManagedPtr :: AnnotatedCommit -> ManagedPtr AnnotatedCommit
toManagedPtr (AnnotatedCommit ManagedPtr AnnotatedCommit
p) = ManagedPtr AnnotatedCommit
p

foreign import ccall "ggit_annotated_commit_get_type" c_ggit_annotated_commit_get_type :: 
    IO GType

type instance O.ParentTypes AnnotatedCommit = '[]
instance O.HasParentTypes AnnotatedCommit

instance B.Types.TypedObject AnnotatedCommit where
    glibType :: IO GType
glibType = IO GType
c_ggit_annotated_commit_get_type

instance B.Types.GBoxed AnnotatedCommit

-- | Convert 'AnnotatedCommit' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe AnnotatedCommit) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ggit_annotated_commit_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AnnotatedCommit -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AnnotatedCommit
P.Nothing = Ptr GValue -> Ptr AnnotatedCommit -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr AnnotatedCommit
forall a. Ptr a
FP.nullPtr :: FP.Ptr AnnotatedCommit)
    gvalueSet_ Ptr GValue
gv (P.Just AnnotatedCommit
obj) = AnnotatedCommit -> (Ptr AnnotatedCommit -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AnnotatedCommit
obj (Ptr GValue -> Ptr AnnotatedCommit -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AnnotatedCommit)
gvalueGet_ Ptr GValue
gv = do
        Ptr AnnotatedCommit
ptr <- Ptr GValue -> IO (Ptr AnnotatedCommit)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr AnnotatedCommit)
        if Ptr AnnotatedCommit
ptr Ptr AnnotatedCommit -> Ptr AnnotatedCommit -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AnnotatedCommit
forall a. Ptr a
FP.nullPtr
        then AnnotatedCommit -> Maybe AnnotatedCommit
forall a. a -> Maybe a
P.Just (AnnotatedCommit -> Maybe AnnotatedCommit)
-> IO AnnotatedCommit -> IO (Maybe AnnotatedCommit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AnnotatedCommit -> AnnotatedCommit)
-> Ptr AnnotatedCommit -> IO AnnotatedCommit
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr AnnotatedCommit -> AnnotatedCommit
AnnotatedCommit Ptr AnnotatedCommit
ptr
        else Maybe AnnotatedCommit -> IO (Maybe AnnotatedCommit)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AnnotatedCommit
forall a. Maybe a
P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AnnotatedCommit
type instance O.AttributeList AnnotatedCommit = AnnotatedCommitAttributeList
type AnnotatedCommitAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method AnnotatedCommit::new_from_ref
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "repository"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "Repository" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the repository" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ref"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Ref" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the reference to use to lookup the git_annotated_commit"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Ggit" , name = "AnnotatedCommit" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_annotated_commit_new_from_ref" ggit_annotated_commit_new_from_ref :: 
    Ptr Ggit.Repository.Repository ->       -- repository : TInterface (Name {namespace = "Ggit", name = "Repository"})
    Ptr Ggit.Ref.Ref ->                     -- ref : TInterface (Name {namespace = "Ggit", name = "Ref"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr AnnotatedCommit)

-- | Create a GgitAnnotatedCommit from the given reference
annotatedCommitNewFromRef ::
    (B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Ref.IsRef b) =>
    a
    -- ^ /@repository@/: the repository
    -> b
    -- ^ /@ref@/: the reference to use to lookup the git_annotated_commit
    -> m AnnotatedCommit
    -- ^ __Returns:__ a t'GI.Ggit.Structs.AnnotatedCommit.AnnotatedCommit'. /(Can throw 'Data.GI.Base.GError.GError')/
annotatedCommitNewFromRef :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRepository a, IsRef b) =>
a -> b -> m AnnotatedCommit
annotatedCommitNewFromRef a
repository b
ref = IO AnnotatedCommit -> m AnnotatedCommit
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AnnotatedCommit -> m AnnotatedCommit)
-> IO AnnotatedCommit -> m AnnotatedCommit
forall a b. (a -> b) -> a -> b
$ do
    Ptr Repository
repository' <- a -> IO (Ptr Repository)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repository
    Ptr Ref
ref' <- b -> IO (Ptr Ref)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
ref
    IO AnnotatedCommit -> IO () -> IO AnnotatedCommit
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr AnnotatedCommit
result <- (Ptr (Ptr GError) -> IO (Ptr AnnotatedCommit))
-> IO (Ptr AnnotatedCommit)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr AnnotatedCommit))
 -> IO (Ptr AnnotatedCommit))
-> (Ptr (Ptr GError) -> IO (Ptr AnnotatedCommit))
-> IO (Ptr AnnotatedCommit)
forall a b. (a -> b) -> a -> b
$ Ptr Repository
-> Ptr Ref -> Ptr (Ptr GError) -> IO (Ptr AnnotatedCommit)
ggit_annotated_commit_new_from_ref Ptr Repository
repository' Ptr Ref
ref'
        Text -> Ptr AnnotatedCommit -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotatedCommitNewFromRef" Ptr AnnotatedCommit
result
        AnnotatedCommit
result' <- ((ManagedPtr AnnotatedCommit -> AnnotatedCommit)
-> Ptr AnnotatedCommit -> IO AnnotatedCommit
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AnnotatedCommit -> AnnotatedCommit
AnnotatedCommit) Ptr AnnotatedCommit
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repository
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
ref
        AnnotatedCommit -> IO AnnotatedCommit
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnotatedCommit
result'
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method AnnotatedCommit::get_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "annotated_commit"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "AnnotatedCommit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitAnnotatedCommit."
--                 , 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_annotated_commit_get_id" ggit_annotated_commit_get_id :: 
    Ptr AnnotatedCommit ->                  -- annotated_commit : TInterface (Name {namespace = "Ggit", name = "AnnotatedCommit"})
    IO (Ptr Ggit.OId.OId)

-- | Gets the commit ID that the given /@annotatedCommit@/ refs to.
annotatedCommitGetId ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AnnotatedCommit
    -- ^ /@annotatedCommit@/: a t'GI.Ggit.Structs.AnnotatedCommit.AnnotatedCommit'.
    -> m (Maybe Ggit.OId.OId)
    -- ^ __Returns:__ the commit ID that the given /@annotatedCommit@/ refs to or 'P.Nothing'.
annotatedCommitGetId :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AnnotatedCommit -> m (Maybe OId)
annotatedCommitGetId AnnotatedCommit
annotatedCommit = IO (Maybe OId) -> m (Maybe OId)
forall a. IO a -> m a
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 AnnotatedCommit
annotatedCommit' <- AnnotatedCommit -> IO (Ptr AnnotatedCommit)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AnnotatedCommit
annotatedCommit
    Ptr OId
result <- Ptr AnnotatedCommit -> IO (Ptr OId)
ggit_annotated_commit_get_id Ptr AnnotatedCommit
annotatedCommit'
    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
$ \Ptr OId
result' -> do
        OId
result'' <- ((ManagedPtr OId -> OId) -> Ptr OId -> IO OId
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr OId -> OId
Ggit.OId.OId) Ptr OId
result'
        OId -> IO OId
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return OId
result''
    AnnotatedCommit -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AnnotatedCommit
annotatedCommit
    Maybe OId -> IO (Maybe OId)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OId
maybeResult

#if defined(ENABLE_OVERLOADING)
data AnnotatedCommitGetIdMethodInfo
instance (signature ~ (m (Maybe Ggit.OId.OId)), MonadIO m) => O.OverloadedMethod AnnotatedCommitGetIdMethodInfo AnnotatedCommit signature where
    overloadedMethod = annotatedCommitGetId

instance O.OverloadedMethodInfo AnnotatedCommitGetIdMethodInfo AnnotatedCommit where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.AnnotatedCommit.annotatedCommitGetId",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Structs-AnnotatedCommit.html#v:annotatedCommitGetId"
        })


#endif

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

foreign import ccall "ggit_annotated_commit_ref" ggit_annotated_commit_ref :: 
    Ptr AnnotatedCommit ->                  -- annotated_commit : TInterface (Name {namespace = "Ggit", name = "AnnotatedCommit"})
    IO (Ptr AnnotatedCommit)

-- | Atomically increments the reference count of /@annotatedCommit@/ by one.
-- This function is MT-safe and may be called from any thread.
annotatedCommitRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AnnotatedCommit
    -- ^ /@annotatedCommit@/: a t'GI.Ggit.Structs.AnnotatedCommit.AnnotatedCommit'.
    -> m (Maybe AnnotatedCommit)
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Structs.AnnotatedCommit.AnnotatedCommit' or 'P.Nothing'.
annotatedCommitRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AnnotatedCommit -> m (Maybe AnnotatedCommit)
annotatedCommitRef AnnotatedCommit
annotatedCommit = IO (Maybe AnnotatedCommit) -> m (Maybe AnnotatedCommit)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AnnotatedCommit) -> m (Maybe AnnotatedCommit))
-> IO (Maybe AnnotatedCommit) -> m (Maybe AnnotatedCommit)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotatedCommit
annotatedCommit' <- AnnotatedCommit -> IO (Ptr AnnotatedCommit)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AnnotatedCommit
annotatedCommit
    Ptr AnnotatedCommit
result <- Ptr AnnotatedCommit -> IO (Ptr AnnotatedCommit)
ggit_annotated_commit_ref Ptr AnnotatedCommit
annotatedCommit'
    Maybe AnnotatedCommit
maybeResult <- Ptr AnnotatedCommit
-> (Ptr AnnotatedCommit -> IO AnnotatedCommit)
-> IO (Maybe AnnotatedCommit)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AnnotatedCommit
result ((Ptr AnnotatedCommit -> IO AnnotatedCommit)
 -> IO (Maybe AnnotatedCommit))
-> (Ptr AnnotatedCommit -> IO AnnotatedCommit)
-> IO (Maybe AnnotatedCommit)
forall a b. (a -> b) -> a -> b
$ \Ptr AnnotatedCommit
result' -> do
        AnnotatedCommit
result'' <- ((ManagedPtr AnnotatedCommit -> AnnotatedCommit)
-> Ptr AnnotatedCommit -> IO AnnotatedCommit
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr AnnotatedCommit -> AnnotatedCommit
AnnotatedCommit) Ptr AnnotatedCommit
result'
        AnnotatedCommit -> IO AnnotatedCommit
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnotatedCommit
result''
    AnnotatedCommit -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AnnotatedCommit
annotatedCommit
    Maybe AnnotatedCommit -> IO (Maybe AnnotatedCommit)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AnnotatedCommit
maybeResult

#if defined(ENABLE_OVERLOADING)
data AnnotatedCommitRefMethodInfo
instance (signature ~ (m (Maybe AnnotatedCommit)), MonadIO m) => O.OverloadedMethod AnnotatedCommitRefMethodInfo AnnotatedCommit signature where
    overloadedMethod = annotatedCommitRef

instance O.OverloadedMethodInfo AnnotatedCommitRefMethodInfo AnnotatedCommit where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.AnnotatedCommit.annotatedCommitRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Structs-AnnotatedCommit.html#v:annotatedCommitRef"
        })


#endif

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

foreign import ccall "ggit_annotated_commit_unref" ggit_annotated_commit_unref :: 
    Ptr AnnotatedCommit ->                  -- annotated_commit : TInterface (Name {namespace = "Ggit", name = "AnnotatedCommit"})
    IO ()

-- | Atomically decrements the reference count of /@annotatedCommit@/ by one.
-- If the reference count drops to 0, /@annotatedCommit@/ is freed.
annotatedCommitUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AnnotatedCommit
    -- ^ /@annotatedCommit@/: a t'GI.Ggit.Structs.AnnotatedCommit.AnnotatedCommit'.
    -> m ()
annotatedCommitUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AnnotatedCommit -> m ()
annotatedCommitUnref AnnotatedCommit
annotatedCommit = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotatedCommit
annotatedCommit' <- AnnotatedCommit -> IO (Ptr AnnotatedCommit)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AnnotatedCommit
annotatedCommit
    Ptr AnnotatedCommit -> IO ()
ggit_annotated_commit_unref Ptr AnnotatedCommit
annotatedCommit'
    AnnotatedCommit -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AnnotatedCommit
annotatedCommit
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AnnotatedCommitUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AnnotatedCommitUnrefMethodInfo AnnotatedCommit signature where
    overloadedMethod = annotatedCommitUnref

instance O.OverloadedMethodInfo AnnotatedCommitUnrefMethodInfo AnnotatedCommit where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.AnnotatedCommit.annotatedCommitUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Structs-AnnotatedCommit.html#v:annotatedCommitUnref"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAnnotatedCommitMethod (t :: Symbol) (o :: *) :: * where
    ResolveAnnotatedCommitMethod "ref" o = AnnotatedCommitRefMethodInfo
    ResolveAnnotatedCommitMethod "unref" o = AnnotatedCommitUnrefMethodInfo
    ResolveAnnotatedCommitMethod "getId" o = AnnotatedCommitGetIdMethodInfo
    ResolveAnnotatedCommitMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveAnnotatedCommitMethod t AnnotatedCommit, O.OverloadedMethod info AnnotatedCommit p, R.HasField t AnnotatedCommit p) => R.HasField t AnnotatedCommit p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveAnnotatedCommitMethod t AnnotatedCommit, O.OverloadedMethodInfo info AnnotatedCommit) => OL.IsLabel t (O.MethodProxy info AnnotatedCommit) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif