{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult' gives a single result from an
-- 'GI.OSTree.Interfaces.RepoFinder.repoFinderResolveAsync' or 'GI.OSTree.Functions.repoFinderResolveAllAsync'
-- operation. This represents a single remote which provides none, some or all
-- of the refs being resolved. The structure includes various bits of metadata
-- which allow 'GI.OSTree.Objects.Repo.repoPullFromRemotesAsync' (for example) to prioritise
-- how to pull the refs.
-- 
-- An t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult' is immutable after construction.
-- 
-- The /@priority@/ is used as one input of many to ordering functions like
-- 'GI.OSTree.Structs.RepoFinderResult.repoFinderResultCompare'.
-- 
-- /@refToChecksum@/ indicates which refs (out of the ones queried for as inputs
-- to 'GI.OSTree.Interfaces.RepoFinder.repoFinderResolveAsync') are provided by this remote. The refs
-- are present as keys (of type t'GI.OSTree.Structs.CollectionRef.CollectionRef'), and the corresponding values
-- are the checksums of the commits the remote currently has for those refs. (These
-- might not be the latest commits available out of all results.) A
-- checksum may be 'P.Nothing' if the remote does not advertise the corresponding ref.
-- After 'GI.OSTree.Interfaces.RepoFinder.repoFinderResolveAsync' has been called, the commit metadata
-- should be available locally, so the details for each checksum can be looked
-- up using 'GI.OSTree.Objects.Repo.repoLoadCommit'.
-- 
-- /@refToTimestamp@/ provides timestamps for the set of refs in
-- /@refToChecksum@/. The refs are keys (of type t'GI.OSTree.Structs.CollectionRef.CollectionRef') and the
-- values are guint64 pointers with the timestamp associated with the checksum
-- provided in /@refToChecksum@/. /@refToTimestamp@/ can be 'P.Nothing', and when it\'s
-- not, the timestamps are zero when any of the following conditions are met:
-- (1) the override-commit-ids option was used on
-- ostree_repo_find_remotes_async (2) there was an error in trying to get the
-- commit metadata (3) the checksum for this ref is 'P.Nothing' in /@refToChecksum@/.
-- 
-- /Since: 2018.6/

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

module GI.OSTree.Structs.RepoFinderResult
    ( 

-- * Exported types
    RepoFinderResult(..)                    ,
    newZeroRepoFinderResult                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [compare]("GI.OSTree.Structs.RepoFinderResult#g:method:compare"), [dup]("GI.OSTree.Structs.RepoFinderResult#g:method:dup"), [free]("GI.OSTree.Structs.RepoFinderResult#g:method:free").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveRepoFinderResultMethod           ,
#endif

-- ** compare #method:compare#

#if defined(ENABLE_OVERLOADING)
    RepoFinderResultCompareMethodInfo       ,
#endif
    repoFinderResultCompare                 ,


-- ** dup #method:dup#

#if defined(ENABLE_OVERLOADING)
    RepoFinderResultDupMethodInfo           ,
#endif
    repoFinderResultDup                     ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    RepoFinderResultFreeMethodInfo          ,
#endif
    repoFinderResultFree                    ,


-- ** freev #method:freev#

    repoFinderResultFreev                   ,




 -- * Properties


-- ** finder #attr:finder#
-- | the t'GI.OSTree.Interfaces.RepoFinder.RepoFinder' instance which produced this result

    clearRepoFinderResultFinder             ,
    getRepoFinderResultFinder               ,
#if defined(ENABLE_OVERLOADING)
    repoFinderResult_finder                 ,
#endif
    setRepoFinderResultFinder               ,


-- ** priority #attr:priority#
-- | static priority of the result, where higher numbers indicate lower
--    priority

    getRepoFinderResultPriority             ,
#if defined(ENABLE_OVERLOADING)
    repoFinderResult_priority               ,
#endif
    setRepoFinderResultPriority             ,


-- ** remote #attr:remote#
-- | t'GI.OSTree.Structs.Remote.Remote' which contains the transport details for the result,
--    such as its URI and GPG key

    clearRepoFinderResultRemote             ,
    getRepoFinderResultRemote               ,
#if defined(ENABLE_OVERLOADING)
    repoFinderResult_remote                 ,
#endif
    setRepoFinderResultRemote               ,


-- ** summaryLastModified #attr:summaryLastModified#
-- | Unix timestamp (seconds since the epoch, UTC) when
--    the summary file on the remote was last modified, or @0@ if unknown

    getRepoFinderResultSummaryLastModified  ,
#if defined(ENABLE_OVERLOADING)
    repoFinderResult_summaryLastModified    ,
#endif
    setRepoFinderResultSummaryLastModified  ,




    ) 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.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.OSTree.Interfaces.RepoFinder as OSTree.RepoFinder
import {-# SOURCE #-} qualified GI.OSTree.Structs.Remote as OSTree.Remote

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

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

foreign import ccall "ostree_repo_finder_result_get_type" c_ostree_repo_finder_result_get_type :: 
    IO GType

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

instance B.Types.TypedObject RepoFinderResult where
    glibType :: IO GType
glibType = IO GType
c_ostree_repo_finder_result_get_type

instance B.Types.GBoxed RepoFinderResult

-- | Convert 'RepoFinderResult' 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 RepoFinderResult) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ostree_repo_finder_result_get_type
    gvalueSet_ :: Ptr GValue -> Maybe RepoFinderResult -> IO ()
gvalueSet_ Ptr GValue
gv Maybe RepoFinderResult
P.Nothing = Ptr GValue -> Ptr RepoFinderResult -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr RepoFinderResult
forall a. Ptr a
FP.nullPtr :: FP.Ptr RepoFinderResult)
    gvalueSet_ Ptr GValue
gv (P.Just RepoFinderResult
obj) = RepoFinderResult -> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RepoFinderResult
obj (Ptr GValue -> Ptr RepoFinderResult -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe RepoFinderResult)
gvalueGet_ Ptr GValue
gv = do
        Ptr RepoFinderResult
ptr <- Ptr GValue -> IO (Ptr RepoFinderResult)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr RepoFinderResult)
        if Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Ptr RepoFinderResult -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr RepoFinderResult
forall a. Ptr a
FP.nullPtr
        then RepoFinderResult -> Maybe RepoFinderResult
forall a. a -> Maybe a
P.Just (RepoFinderResult -> Maybe RepoFinderResult)
-> IO RepoFinderResult -> IO (Maybe RepoFinderResult)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr RepoFinderResult -> RepoFinderResult)
-> Ptr RepoFinderResult -> IO RepoFinderResult
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr RepoFinderResult -> RepoFinderResult
RepoFinderResult Ptr RepoFinderResult
ptr
        else Maybe RepoFinderResult -> IO (Maybe RepoFinderResult)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RepoFinderResult
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `RepoFinderResult` struct initialized to zero.
newZeroRepoFinderResult :: MonadIO m => m RepoFinderResult
newZeroRepoFinderResult :: forall (m :: * -> *). MonadIO m => m RepoFinderResult
newZeroRepoFinderResult = IO RepoFinderResult -> m RepoFinderResult
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RepoFinderResult -> m RepoFinderResult)
-> IO RepoFinderResult -> m RepoFinderResult
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr RepoFinderResult)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
72 IO (Ptr RepoFinderResult)
-> (Ptr RepoFinderResult -> IO RepoFinderResult)
-> IO RepoFinderResult
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr RepoFinderResult -> RepoFinderResult)
-> Ptr RepoFinderResult -> IO RepoFinderResult
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RepoFinderResult -> RepoFinderResult
RepoFinderResult

instance tag ~ 'AttrSet => Constructible RepoFinderResult tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr RepoFinderResult -> RepoFinderResult)
-> [AttrOp RepoFinderResult tag] -> m RepoFinderResult
new ManagedPtr RepoFinderResult -> RepoFinderResult
_ [AttrOp RepoFinderResult tag]
attrs = do
        RepoFinderResult
o <- m RepoFinderResult
forall (m :: * -> *). MonadIO m => m RepoFinderResult
newZeroRepoFinderResult
        RepoFinderResult -> [AttrOp RepoFinderResult 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set RepoFinderResult
o [AttrOp RepoFinderResult tag]
[AttrOp RepoFinderResult 'AttrSet]
attrs
        RepoFinderResult -> m RepoFinderResult
forall (m :: * -> *) a. Monad m => a -> m a
return RepoFinderResult
o


-- | Get the value of the “@remote@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' repoFinderResult #remote
-- @
getRepoFinderResultRemote :: MonadIO m => RepoFinderResult -> m (Maybe OSTree.Remote.Remote)
getRepoFinderResultRemote :: forall (m :: * -> *).
MonadIO m =>
RepoFinderResult -> m (Maybe Remote)
getRepoFinderResultRemote RepoFinderResult
s = IO (Maybe Remote) -> m (Maybe Remote)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Remote) -> m (Maybe Remote))
-> IO (Maybe Remote) -> m (Maybe Remote)
forall a b. (a -> b) -> a -> b
$ RepoFinderResult
-> (Ptr RepoFinderResult -> IO (Maybe Remote)) -> IO (Maybe Remote)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO (Maybe Remote)) -> IO (Maybe Remote))
-> (Ptr RepoFinderResult -> IO (Maybe Remote)) -> IO (Maybe Remote)
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr Remote
val <- Ptr (Ptr Remote) -> IO (Ptr Remote)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr (Ptr Remote)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (Ptr OSTree.Remote.Remote)
    Maybe Remote
result <- Ptr Remote -> (Ptr Remote -> IO Remote) -> IO (Maybe Remote)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Remote
val ((Ptr Remote -> IO Remote) -> IO (Maybe Remote))
-> (Ptr Remote -> IO Remote) -> IO (Maybe Remote)
forall a b. (a -> b) -> a -> b
$ \Ptr Remote
val' -> do
        Remote
val'' <- ((ManagedPtr Remote -> Remote) -> Ptr Remote -> IO Remote
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Remote -> Remote
OSTree.Remote.Remote) Ptr Remote
val'
        Remote -> IO Remote
forall (m :: * -> *) a. Monad m => a -> m a
return Remote
val''
    Maybe Remote -> IO (Maybe Remote)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Remote
result

-- | Set the value of the “@remote@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' repoFinderResult [ #remote 'Data.GI.Base.Attributes.:=' value ]
-- @
setRepoFinderResultRemote :: MonadIO m => RepoFinderResult -> Ptr OSTree.Remote.Remote -> m ()
setRepoFinderResultRemote :: forall (m :: * -> *).
MonadIO m =>
RepoFinderResult -> Ptr Remote -> m ()
setRepoFinderResultRemote RepoFinderResult
s Ptr Remote
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RepoFinderResult -> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO ()) -> IO ())
-> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr (Ptr Remote) -> Ptr Remote -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr (Ptr Remote)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr Remote
val :: Ptr OSTree.Remote.Remote)

-- | Set the value of the “@remote@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #remote
-- @
clearRepoFinderResultRemote :: MonadIO m => RepoFinderResult -> m ()
clearRepoFinderResultRemote :: forall (m :: * -> *). MonadIO m => RepoFinderResult -> m ()
clearRepoFinderResultRemote RepoFinderResult
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RepoFinderResult -> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO ()) -> IO ())
-> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr (Ptr Remote) -> Ptr Remote -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr (Ptr Remote)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr Remote
forall a. Ptr a
FP.nullPtr :: Ptr OSTree.Remote.Remote)

#if defined(ENABLE_OVERLOADING)
data RepoFinderResultRemoteFieldInfo
instance AttrInfo RepoFinderResultRemoteFieldInfo where
    type AttrBaseTypeConstraint RepoFinderResultRemoteFieldInfo = (~) RepoFinderResult
    type AttrAllowedOps RepoFinderResultRemoteFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint RepoFinderResultRemoteFieldInfo = (~) (Ptr OSTree.Remote.Remote)
    type AttrTransferTypeConstraint RepoFinderResultRemoteFieldInfo = (~)(Ptr OSTree.Remote.Remote)
    type AttrTransferType RepoFinderResultRemoteFieldInfo = (Ptr OSTree.Remote.Remote)
    type AttrGetType RepoFinderResultRemoteFieldInfo = Maybe OSTree.Remote.Remote
    type AttrLabel RepoFinderResultRemoteFieldInfo = "remote"
    type AttrOrigin RepoFinderResultRemoteFieldInfo = RepoFinderResult
    attrGet = getRepoFinderResultRemote
    attrSet = setRepoFinderResultRemote
    attrConstruct = undefined
    attrClear = clearRepoFinderResultRemote
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoFinderResult.remote"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoFinderResult.html#g:attr:remote"
        })

repoFinderResult_remote :: AttrLabelProxy "remote"
repoFinderResult_remote = AttrLabelProxy

#endif


-- | Get the value of the “@finder@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' repoFinderResult #finder
-- @
getRepoFinderResultFinder :: MonadIO m => RepoFinderResult -> m (Maybe OSTree.RepoFinder.RepoFinder)
getRepoFinderResultFinder :: forall (m :: * -> *).
MonadIO m =>
RepoFinderResult -> m (Maybe RepoFinder)
getRepoFinderResultFinder RepoFinderResult
s = IO (Maybe RepoFinder) -> m (Maybe RepoFinder)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe RepoFinder) -> m (Maybe RepoFinder))
-> IO (Maybe RepoFinder) -> m (Maybe RepoFinder)
forall a b. (a -> b) -> a -> b
$ RepoFinderResult
-> (Ptr RepoFinderResult -> IO (Maybe RepoFinder))
-> IO (Maybe RepoFinder)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO (Maybe RepoFinder))
 -> IO (Maybe RepoFinder))
-> (Ptr RepoFinderResult -> IO (Maybe RepoFinder))
-> IO (Maybe RepoFinder)
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr RepoFinder
val <- Ptr (Ptr RepoFinder) -> IO (Ptr RepoFinder)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr (Ptr RepoFinder)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr OSTree.RepoFinder.RepoFinder)
    Maybe RepoFinder
result <- Ptr RepoFinder
-> (Ptr RepoFinder -> IO RepoFinder) -> IO (Maybe RepoFinder)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr RepoFinder
val ((Ptr RepoFinder -> IO RepoFinder) -> IO (Maybe RepoFinder))
-> (Ptr RepoFinder -> IO RepoFinder) -> IO (Maybe RepoFinder)
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinder
val' -> do
        RepoFinder
val'' <- ((ManagedPtr RepoFinder -> RepoFinder)
-> Ptr RepoFinder -> IO RepoFinder
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr RepoFinder -> RepoFinder
OSTree.RepoFinder.RepoFinder) Ptr RepoFinder
val'
        RepoFinder -> IO RepoFinder
forall (m :: * -> *) a. Monad m => a -> m a
return RepoFinder
val''
    Maybe RepoFinder -> IO (Maybe RepoFinder)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RepoFinder
result

-- | Set the value of the “@finder@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' repoFinderResult [ #finder 'Data.GI.Base.Attributes.:=' value ]
-- @
setRepoFinderResultFinder :: MonadIO m => RepoFinderResult -> Ptr OSTree.RepoFinder.RepoFinder -> m ()
setRepoFinderResultFinder :: forall (m :: * -> *).
MonadIO m =>
RepoFinderResult -> Ptr RepoFinder -> m ()
setRepoFinderResultFinder RepoFinderResult
s Ptr RepoFinder
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RepoFinderResult -> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO ()) -> IO ())
-> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr (Ptr RepoFinder) -> Ptr RepoFinder -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr (Ptr RepoFinder)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr RepoFinder
val :: Ptr OSTree.RepoFinder.RepoFinder)

-- | Set the value of the “@finder@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #finder
-- @
clearRepoFinderResultFinder :: MonadIO m => RepoFinderResult -> m ()
clearRepoFinderResultFinder :: forall (m :: * -> *). MonadIO m => RepoFinderResult -> m ()
clearRepoFinderResultFinder RepoFinderResult
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RepoFinderResult -> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO ()) -> IO ())
-> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr (Ptr RepoFinder) -> Ptr RepoFinder -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr (Ptr RepoFinder)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr RepoFinder
forall a. Ptr a
FP.nullPtr :: Ptr OSTree.RepoFinder.RepoFinder)

#if defined(ENABLE_OVERLOADING)
data RepoFinderResultFinderFieldInfo
instance AttrInfo RepoFinderResultFinderFieldInfo where
    type AttrBaseTypeConstraint RepoFinderResultFinderFieldInfo = (~) RepoFinderResult
    type AttrAllowedOps RepoFinderResultFinderFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint RepoFinderResultFinderFieldInfo = (~) (Ptr OSTree.RepoFinder.RepoFinder)
    type AttrTransferTypeConstraint RepoFinderResultFinderFieldInfo = (~)(Ptr OSTree.RepoFinder.RepoFinder)
    type AttrTransferType RepoFinderResultFinderFieldInfo = (Ptr OSTree.RepoFinder.RepoFinder)
    type AttrGetType RepoFinderResultFinderFieldInfo = Maybe OSTree.RepoFinder.RepoFinder
    type AttrLabel RepoFinderResultFinderFieldInfo = "finder"
    type AttrOrigin RepoFinderResultFinderFieldInfo = RepoFinderResult
    attrGet = getRepoFinderResultFinder
    attrSet = setRepoFinderResultFinder
    attrConstruct = undefined
    attrClear = clearRepoFinderResultFinder
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoFinderResult.finder"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoFinderResult.html#g:attr:finder"
        })

repoFinderResult_finder :: AttrLabelProxy "finder"
repoFinderResult_finder = AttrLabelProxy

#endif


-- | Get the value of the “@priority@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' repoFinderResult #priority
-- @
getRepoFinderResultPriority :: MonadIO m => RepoFinderResult -> m Int32
getRepoFinderResultPriority :: forall (m :: * -> *). MonadIO m => RepoFinderResult -> m Int32
getRepoFinderResultPriority RepoFinderResult
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ RepoFinderResult -> (Ptr RepoFinderResult -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO Int32) -> IO Int32)
-> (Ptr RepoFinderResult -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@priority@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' repoFinderResult [ #priority 'Data.GI.Base.Attributes.:=' value ]
-- @
setRepoFinderResultPriority :: MonadIO m => RepoFinderResult -> Int32 -> m ()
setRepoFinderResultPriority :: forall (m :: * -> *).
MonadIO m =>
RepoFinderResult -> Int32 -> m ()
setRepoFinderResultPriority RepoFinderResult
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RepoFinderResult -> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO ()) -> IO ())
-> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data RepoFinderResultPriorityFieldInfo
instance AttrInfo RepoFinderResultPriorityFieldInfo where
    type AttrBaseTypeConstraint RepoFinderResultPriorityFieldInfo = (~) RepoFinderResult
    type AttrAllowedOps RepoFinderResultPriorityFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RepoFinderResultPriorityFieldInfo = (~) Int32
    type AttrTransferTypeConstraint RepoFinderResultPriorityFieldInfo = (~)Int32
    type AttrTransferType RepoFinderResultPriorityFieldInfo = Int32
    type AttrGetType RepoFinderResultPriorityFieldInfo = Int32
    type AttrLabel RepoFinderResultPriorityFieldInfo = "priority"
    type AttrOrigin RepoFinderResultPriorityFieldInfo = RepoFinderResult
    attrGet = getRepoFinderResultPriority
    attrSet = setRepoFinderResultPriority
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoFinderResult.priority"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoFinderResult.html#g:attr:priority"
        })

repoFinderResult_priority :: AttrLabelProxy "priority"
repoFinderResult_priority = AttrLabelProxy

#endif


-- XXX Skipped attribute for "RepoFinderResult:ref_to_checksum"
-- Not implemented: GHashTable element of type TInterface (Name {namespace = "OSTree", name = "CollectionRef"}) unsupported.
-- | Get the value of the “@summary_last_modified@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' repoFinderResult #summaryLastModified
-- @
getRepoFinderResultSummaryLastModified :: MonadIO m => RepoFinderResult -> m Word64
getRepoFinderResultSummaryLastModified :: forall (m :: * -> *). MonadIO m => RepoFinderResult -> m Word64
getRepoFinderResultSummaryLastModified RepoFinderResult
s = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ RepoFinderResult
-> (Ptr RepoFinderResult -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO Word64) -> IO Word64)
-> (Ptr RepoFinderResult -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO Word64
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val

-- | Set the value of the “@summary_last_modified@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' repoFinderResult [ #summaryLastModified 'Data.GI.Base.Attributes.:=' value ]
-- @
setRepoFinderResultSummaryLastModified :: MonadIO m => RepoFinderResult -> Word64 -> m ()
setRepoFinderResultSummaryLastModified :: forall (m :: * -> *).
MonadIO m =>
RepoFinderResult -> Word64 -> m ()
setRepoFinderResultSummaryLastModified RepoFinderResult
s Word64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RepoFinderResult -> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoFinderResult
s ((Ptr RepoFinderResult -> IO ()) -> IO ())
-> (Ptr RepoFinderResult -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RepoFinderResult
ptr -> do
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RepoFinderResult
ptr Ptr RepoFinderResult -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Word64
val :: Word64)

#if defined(ENABLE_OVERLOADING)
data RepoFinderResultSummaryLastModifiedFieldInfo
instance AttrInfo RepoFinderResultSummaryLastModifiedFieldInfo where
    type AttrBaseTypeConstraint RepoFinderResultSummaryLastModifiedFieldInfo = (~) RepoFinderResult
    type AttrAllowedOps RepoFinderResultSummaryLastModifiedFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RepoFinderResultSummaryLastModifiedFieldInfo = (~) Word64
    type AttrTransferTypeConstraint RepoFinderResultSummaryLastModifiedFieldInfo = (~)Word64
    type AttrTransferType RepoFinderResultSummaryLastModifiedFieldInfo = Word64
    type AttrGetType RepoFinderResultSummaryLastModifiedFieldInfo = Word64
    type AttrLabel RepoFinderResultSummaryLastModifiedFieldInfo = "summary_last_modified"
    type AttrOrigin RepoFinderResultSummaryLastModifiedFieldInfo = RepoFinderResult
    attrGet = getRepoFinderResultSummaryLastModified
    attrSet = setRepoFinderResultSummaryLastModified
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoFinderResult.summaryLastModified"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoFinderResult.html#g:attr:summaryLastModified"
        })

repoFinderResult_summaryLastModified :: AttrLabelProxy "summaryLastModified"
repoFinderResult_summaryLastModified = AttrLabelProxy

#endif


-- XXX Skipped attribute for "RepoFinderResult:ref_to_timestamp"
-- Not implemented: GHashTable element of type TInterface (Name {namespace = "OSTree", name = "CollectionRef"}) unsupported.

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RepoFinderResult
type instance O.AttributeList RepoFinderResult = RepoFinderResultAttributeList
type RepoFinderResultAttributeList = ('[ '("remote", RepoFinderResultRemoteFieldInfo), '("finder", RepoFinderResultFinderFieldInfo), '("priority", RepoFinderResultPriorityFieldInfo), '("summaryLastModified", RepoFinderResultSummaryLastModifiedFieldInfo)] :: [(Symbol, *)])
#endif

-- XXX Could not generate method RepoFinderResult::new
-- Not implemented: GHashTable key of type TInterface (Name {namespace = "OSTree", name = "CollectionRef"}) unsupported.
-- method RepoFinderResult::compare
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "RepoFinderResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #OstreeRepoFinderResult"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "RepoFinderResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #OstreeRepoFinderResult"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_finder_result_compare" ostree_repo_finder_result_compare :: 
    Ptr RepoFinderResult ->                 -- a : TInterface (Name {namespace = "OSTree", name = "RepoFinderResult"})
    Ptr RepoFinderResult ->                 -- b : TInterface (Name {namespace = "OSTree", name = "RepoFinderResult"})
    IO Int32

-- | Compare two t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult' instances to work out which one is better
-- to pull from, and hence needs to be ordered before the other.
-- 
-- /Since: 2018.6/
repoFinderResultCompare ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RepoFinderResult
    -- ^ /@a@/: an t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult'
    -> RepoFinderResult
    -- ^ /@b@/: an t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult'
    -> m Int32
    -- ^ __Returns:__ \<0 if /@a@/ is ordered before /@b@/, 0 if they are ordered equally,
    --    >0 if /@b@/ is ordered before /@a@/
repoFinderResultCompare :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RepoFinderResult -> RepoFinderResult -> m Int32
repoFinderResultCompare RepoFinderResult
a RepoFinderResult
b = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFinderResult
a' <- RepoFinderResult -> IO (Ptr RepoFinderResult)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RepoFinderResult
a
    Ptr RepoFinderResult
b' <- RepoFinderResult -> IO (Ptr RepoFinderResult)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RepoFinderResult
b
    Int32
result <- Ptr RepoFinderResult -> Ptr RepoFinderResult -> IO Int32
ostree_repo_finder_result_compare Ptr RepoFinderResult
a' Ptr RepoFinderResult
b'
    RepoFinderResult -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RepoFinderResult
a
    RepoFinderResult -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RepoFinderResult
b
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data RepoFinderResultCompareMethodInfo
instance (signature ~ (RepoFinderResult -> m Int32), MonadIO m) => O.OverloadedMethod RepoFinderResultCompareMethodInfo RepoFinderResult signature where
    overloadedMethod = repoFinderResultCompare

instance O.OverloadedMethodInfo RepoFinderResultCompareMethodInfo RepoFinderResult where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoFinderResult.repoFinderResultCompare",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoFinderResult.html#v:repoFinderResultCompare"
        })


#endif

-- method RepoFinderResult::dup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "result"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "RepoFinderResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #OstreeRepoFinderResult to copy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "OSTree" , name = "RepoFinderResult" })
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_finder_result_dup" ostree_repo_finder_result_dup :: 
    Ptr RepoFinderResult ->                 -- result : TInterface (Name {namespace = "OSTree", name = "RepoFinderResult"})
    IO (Ptr RepoFinderResult)

-- | Copy an t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult'.
-- 
-- /Since: 2018.6/
repoFinderResultDup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RepoFinderResult
    -- ^ /@result@/: an t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult' to copy
    -> m RepoFinderResult
    -- ^ __Returns:__ a newly allocated copy of /@result@/
repoFinderResultDup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RepoFinderResult -> m RepoFinderResult
repoFinderResultDup RepoFinderResult
result_ = IO RepoFinderResult -> m RepoFinderResult
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RepoFinderResult -> m RepoFinderResult)
-> IO RepoFinderResult -> m RepoFinderResult
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFinderResult
result_' <- RepoFinderResult -> IO (Ptr RepoFinderResult)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RepoFinderResult
result_
    Ptr RepoFinderResult
result <- Ptr RepoFinderResult -> IO (Ptr RepoFinderResult)
ostree_repo_finder_result_dup Ptr RepoFinderResult
result_'
    Text -> Ptr RepoFinderResult -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"repoFinderResultDup" Ptr RepoFinderResult
result
    RepoFinderResult
result' <- ((ManagedPtr RepoFinderResult -> RepoFinderResult)
-> Ptr RepoFinderResult -> IO RepoFinderResult
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RepoFinderResult -> RepoFinderResult
RepoFinderResult) Ptr RepoFinderResult
result
    RepoFinderResult -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RepoFinderResult
result_
    RepoFinderResult -> IO RepoFinderResult
forall (m :: * -> *) a. Monad m => a -> m a
return RepoFinderResult
result'

#if defined(ENABLE_OVERLOADING)
data RepoFinderResultDupMethodInfo
instance (signature ~ (m RepoFinderResult), MonadIO m) => O.OverloadedMethod RepoFinderResultDupMethodInfo RepoFinderResult signature where
    overloadedMethod = repoFinderResultDup

instance O.OverloadedMethodInfo RepoFinderResultDupMethodInfo RepoFinderResult where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoFinderResult.repoFinderResultDup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoFinderResult.html#v:repoFinderResultDup"
        })


#endif

-- method RepoFinderResult::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "result"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "RepoFinderResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #OstreeRepoFinderResult"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_finder_result_free" ostree_repo_finder_result_free :: 
    Ptr RepoFinderResult ->                 -- result : TInterface (Name {namespace = "OSTree", name = "RepoFinderResult"})
    IO ()

-- | Free the given /@result@/.
-- 
-- /Since: 2018.6/
repoFinderResultFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RepoFinderResult
    -- ^ /@result@/: an t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult'
    -> m ()
repoFinderResultFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RepoFinderResult -> m ()
repoFinderResultFree RepoFinderResult
result_ = 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 RepoFinderResult
result_' <- RepoFinderResult -> IO (Ptr RepoFinderResult)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed RepoFinderResult
result_
    Ptr RepoFinderResult -> IO ()
ostree_repo_finder_result_free Ptr RepoFinderResult
result_'
    RepoFinderResult -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RepoFinderResult
result_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RepoFinderResultFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RepoFinderResultFreeMethodInfo RepoFinderResult signature where
    overloadedMethod = repoFinderResultFree

instance O.OverloadedMethodInfo RepoFinderResultFreeMethodInfo RepoFinderResult where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoFinderResult.repoFinderResultFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoFinderResult.html#v:repoFinderResultFree"
        })


#endif

-- method RepoFinderResult::freev
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "results"
--           , argType =
--               TCArray
--                 True
--                 (-1)
--                 (-1)
--                 (TInterface
--                    Name { namespace = "OSTree" , name = "RepoFinderResult" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #OstreeRepoFinderResult"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_finder_result_freev" ostree_repo_finder_result_freev :: 
    Ptr (Ptr RepoFinderResult) ->           -- results : TCArray True (-1) (-1) (TInterface (Name {namespace = "OSTree", name = "RepoFinderResult"}))
    IO ()

-- | Free the given /@results@/ array, freeing each element and the container.
-- 
-- /Since: 2018.6/
repoFinderResultFreev ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [RepoFinderResult]
    -- ^ /@results@/: an t'GI.OSTree.Structs.RepoFinderResult.RepoFinderResult'
    -> m ()
repoFinderResultFreev :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[RepoFinderResult] -> m ()
repoFinderResultFreev [RepoFinderResult]
results = 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 RepoFinderResult]
results' <- (RepoFinderResult -> IO (Ptr RepoFinderResult))
-> [RepoFinderResult] -> IO [Ptr RepoFinderResult]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM RepoFinderResult -> IO (Ptr RepoFinderResult)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed [RepoFinderResult]
results
    Ptr (Ptr RepoFinderResult)
results'' <- [Ptr RepoFinderResult] -> IO (Ptr (Ptr RepoFinderResult))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packZeroTerminatedPtrArray [Ptr RepoFinderResult]
results'
    Ptr (Ptr RepoFinderResult) -> IO ()
ostree_repo_finder_result_freev Ptr (Ptr RepoFinderResult)
results''
    (RepoFinderResult -> IO ()) -> [RepoFinderResult] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ RepoFinderResult -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [RepoFinderResult]
results
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRepoFinderResultMethod (t :: Symbol) (o :: *) :: * where
    ResolveRepoFinderResultMethod "compare" o = RepoFinderResultCompareMethodInfo
    ResolveRepoFinderResultMethod "dup" o = RepoFinderResultDupMethodInfo
    ResolveRepoFinderResultMethod "free" o = RepoFinderResultFreeMethodInfo
    ResolveRepoFinderResultMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveRepoFinderResultMethod t RepoFinderResult, O.OverloadedMethod info RepoFinderResult p) => OL.IsLabel t (RepoFinderResult -> 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 ~ ResolveRepoFinderResultMethod t RepoFinderResult, O.OverloadedMethod info RepoFinderResult p, R.HasField t RepoFinderResult p) => R.HasField t RepoFinderResult p where
    getField = O.overloadedMethod @info

#endif

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

#endif