{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.OSTree.Interfaces.RepoFinder
(
RepoFinder(..) ,
IsRepoFinder ,
toRepoFinder ,
#if defined(ENABLE_OVERLOADING)
ResolveRepoFinderMethod ,
#endif
repoFinderResolveAllAsync ,
repoFinderResolveAllFinish ,
#if defined(ENABLE_OVERLOADING)
RepoFinderResolveAsyncMethodInfo ,
#endif
repoFinderResolveAsync ,
#if defined(ENABLE_OVERLOADING)
RepoFinderResolveFinishMethodInfo ,
#endif
repoFinderResolveFinish ,
) 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.Kind as DK
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 qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GLib.Structs.VariantDict as GLib.VariantDict
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
import qualified GI.Gio.Objects.InputStream as Gio.InputStream
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import qualified GI.OSTree.Callbacks as OSTree.Callbacks
import {-# SOURCE #-} qualified GI.OSTree.Enums as OSTree.Enums
import {-# SOURCE #-} qualified GI.OSTree.Flags as OSTree.Flags
import {-# SOURCE #-} qualified GI.OSTree.Interfaces.Sign as OSTree.Sign
import {-# SOURCE #-} qualified GI.OSTree.Objects.AsyncProgress as OSTree.AsyncProgress
import {-# SOURCE #-} qualified GI.OSTree.Objects.ContentWriter as OSTree.ContentWriter
import {-# SOURCE #-} qualified GI.OSTree.Objects.GpgVerifyResult as OSTree.GpgVerifyResult
import {-# SOURCE #-} qualified GI.OSTree.Objects.MutableTree as OSTree.MutableTree
import {-# SOURCE #-} qualified GI.OSTree.Objects.Repo as OSTree.Repo
import {-# SOURCE #-} qualified GI.OSTree.Objects.RepoFile as OSTree.RepoFile
import {-# SOURCE #-} qualified GI.OSTree.Objects.SePolicy as OSTree.SePolicy
import {-# SOURCE #-} qualified GI.OSTree.Structs.CollectionRef as OSTree.CollectionRef
import {-# SOURCE #-} qualified GI.OSTree.Structs.Remote as OSTree.Remote
import {-# SOURCE #-} qualified GI.OSTree.Structs.RepoCheckoutAtOptions as OSTree.RepoCheckoutAtOptions
import {-# SOURCE #-} qualified GI.OSTree.Structs.RepoCommitModifier as OSTree.RepoCommitModifier
import {-# SOURCE #-} qualified GI.OSTree.Structs.RepoDevInoCache as OSTree.RepoDevInoCache
import {-# SOURCE #-} qualified GI.OSTree.Structs.RepoFinderResult as OSTree.RepoFinderResult
import {-# SOURCE #-} qualified GI.OSTree.Structs.RepoPruneOptions as OSTree.RepoPruneOptions
import {-# SOURCE #-} qualified GI.OSTree.Structs.RepoTransactionStats as OSTree.RepoTransactionStats
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.OSTree.Objects.Repo as OSTree.Repo
import {-# SOURCE #-} qualified GI.OSTree.Structs.CollectionRef as OSTree.CollectionRef
import {-# SOURCE #-} qualified GI.OSTree.Structs.RepoFinderResult as OSTree.RepoFinderResult
#endif
newtype RepoFinder = RepoFinder (SP.ManagedPtr RepoFinder)
deriving (RepoFinder -> RepoFinder -> Bool
(RepoFinder -> RepoFinder -> Bool)
-> (RepoFinder -> RepoFinder -> Bool) -> Eq RepoFinder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RepoFinder -> RepoFinder -> Bool
== :: RepoFinder -> RepoFinder -> Bool
$c/= :: RepoFinder -> RepoFinder -> Bool
/= :: RepoFinder -> RepoFinder -> Bool
Eq)
instance SP.ManagedPtrNewtype RepoFinder where
toManagedPtr :: RepoFinder -> ManagedPtr RepoFinder
toManagedPtr (RepoFinder ManagedPtr RepoFinder
p) = ManagedPtr RepoFinder
p
foreign import ccall "ostree_repo_finder_get_type"
c_ostree_repo_finder_get_type :: IO B.Types.GType
instance B.Types.TypedObject RepoFinder where
glibType :: IO GType
glibType = IO GType
c_ostree_repo_finder_get_type
instance B.Types.GObject RepoFinder
class (SP.GObject o, O.IsDescendantOf RepoFinder o) => IsRepoFinder o
instance (SP.GObject o, O.IsDescendantOf RepoFinder o) => IsRepoFinder o
instance O.HasParentTypes RepoFinder
type instance O.ParentTypes RepoFinder = '[GObject.Object.Object]
toRepoFinder :: (MIO.MonadIO m, IsRepoFinder o) => o -> m RepoFinder
toRepoFinder :: forall (m :: * -> *) o.
(MonadIO m, IsRepoFinder o) =>
o -> m RepoFinder
toRepoFinder = IO RepoFinder -> m RepoFinder
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO RepoFinder -> m RepoFinder)
-> (o -> IO RepoFinder) -> o -> m RepoFinder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr RepoFinder -> RepoFinder) -> o -> IO RepoFinder
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr RepoFinder -> RepoFinder
RepoFinder
instance B.GValue.IsGValue (Maybe RepoFinder) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ostree_repo_finder_get_type
gvalueSet_ :: Ptr GValue -> Maybe RepoFinder -> IO ()
gvalueSet_ Ptr GValue
gv Maybe RepoFinder
P.Nothing = Ptr GValue -> Ptr RepoFinder -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr RepoFinder
forall a. Ptr a
FP.nullPtr :: FP.Ptr RepoFinder)
gvalueSet_ Ptr GValue
gv (P.Just RepoFinder
obj) = RepoFinder -> (Ptr RepoFinder -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RepoFinder
obj (Ptr GValue -> Ptr RepoFinder -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe RepoFinder)
gvalueGet_ Ptr GValue
gv = do
Ptr RepoFinder
ptr <- Ptr GValue -> IO (Ptr RepoFinder)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr RepoFinder)
if Ptr RepoFinder
ptr Ptr RepoFinder -> Ptr RepoFinder -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr RepoFinder
forall a. Ptr a
FP.nullPtr
then RepoFinder -> Maybe RepoFinder
forall a. a -> Maybe a
P.Just (RepoFinder -> Maybe RepoFinder)
-> IO RepoFinder -> IO (Maybe RepoFinder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr RepoFinder -> RepoFinder)
-> Ptr RepoFinder -> IO RepoFinder
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr RepoFinder -> RepoFinder
RepoFinder Ptr RepoFinder
ptr
else Maybe RepoFinder -> IO (Maybe RepoFinder)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RepoFinder
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RepoFinder
type instance O.AttributeList RepoFinder = RepoFinderAttributeList
type RepoFinderAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveRepoFinderMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveRepoFinderMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveRepoFinderMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveRepoFinderMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveRepoFinderMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveRepoFinderMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveRepoFinderMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveRepoFinderMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveRepoFinderMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveRepoFinderMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveRepoFinderMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveRepoFinderMethod "resolveAsync" o = RepoFinderResolveAsyncMethodInfo
ResolveRepoFinderMethod "resolveFinish" o = RepoFinderResolveFinishMethodInfo
ResolveRepoFinderMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveRepoFinderMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveRepoFinderMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveRepoFinderMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveRepoFinderMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveRepoFinderMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveRepoFinderMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveRepoFinderMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveRepoFinderMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveRepoFinderMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveRepoFinderMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveRepoFinderMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveRepoFinderMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRepoFinderMethod t RepoFinder, O.OverloadedMethod info RepoFinder p) => OL.IsLabel t (RepoFinder -> 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 ~ ResolveRepoFinderMethod t RepoFinder, O.OverloadedMethod info RepoFinder p, R.HasField t RepoFinder p) => R.HasField t RepoFinder p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveRepoFinderMethod t RepoFinder, O.OverloadedMethodInfo info RepoFinder) => OL.IsLabel t (O.MethodProxy info RepoFinder) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "ostree_repo_finder_resolve_async" ostree_repo_finder_resolve_async ::
Ptr RepoFinder ->
Ptr (Ptr OSTree.CollectionRef.CollectionRef) ->
Ptr OSTree.Repo.Repo ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
repoFinderResolveAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsRepoFinder a, OSTree.Repo.IsRepo b, Gio.Cancellable.IsCancellable c) =>
a
-> [OSTree.CollectionRef.CollectionRef]
-> b
-> Maybe (c)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
repoFinderResolveAsync :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsRepoFinder a, IsRepo b,
IsCancellable c) =>
a
-> [CollectionRef]
-> b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
repoFinderResolveAsync a
self [CollectionRef]
refs b
parentRepo Maybe c
cancellable Maybe AsyncReadyCallback
callback = 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 RepoFinder
self' <- a -> IO (Ptr RepoFinder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
[Ptr CollectionRef]
refs' <- (CollectionRef -> IO (Ptr CollectionRef))
-> [CollectionRef] -> IO [Ptr CollectionRef]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CollectionRef -> IO (Ptr CollectionRef)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [CollectionRef]
refs
Ptr (Ptr CollectionRef)
refs'' <- [Ptr CollectionRef] -> IO (Ptr (Ptr CollectionRef))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packZeroTerminatedPtrArray [Ptr CollectionRef]
refs'
Ptr Repo
parentRepo' <- b -> IO (Ptr Repo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
parentRepo
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr RepoFinder
-> Ptr (Ptr CollectionRef)
-> Ptr Repo
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
ostree_repo_finder_resolve_async Ptr RepoFinder
self' Ptr (Ptr CollectionRef)
refs'' Ptr Repo
parentRepo' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
(CollectionRef -> IO ()) -> [CollectionRef] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CollectionRef -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [CollectionRef]
refs
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
parentRepo
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr (Ptr CollectionRef) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CollectionRef)
refs''
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RepoFinderResolveAsyncMethodInfo
instance (signature ~ ([OSTree.CollectionRef.CollectionRef] -> b -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsRepoFinder a, OSTree.Repo.IsRepo b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod RepoFinderResolveAsyncMethodInfo a signature where
overloadedMethod = repoFinderResolveAsync
instance O.OverloadedMethodInfo RepoFinderResolveAsyncMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.OSTree.Interfaces.RepoFinder.repoFinderResolveAsync",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.19/docs/GI-OSTree-Interfaces-RepoFinder.html#v:repoFinderResolveAsync"
})
#endif
foreign import ccall "ostree_repo_finder_resolve_finish" ostree_repo_finder_resolve_finish ::
Ptr RepoFinder ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr (GPtrArray (Ptr OSTree.RepoFinderResult.RepoFinderResult)))
repoFinderResolveFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsRepoFinder a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m [OSTree.RepoFinderResult.RepoFinderResult]
repoFinderResolveFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRepoFinder a, IsAsyncResult b) =>
a -> b -> m [RepoFinderResult]
repoFinderResolveFinish a
self b
result_ = IO [RepoFinderResult] -> m [RepoFinderResult]
forall a. IO a -> m a
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 RepoFinder
self' <- a -> IO (Ptr RepoFinder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO [RepoFinderResult] -> IO () -> IO [RepoFinderResult]
forall a b. IO a -> IO b -> IO a
onException (do
Ptr (GPtrArray (Ptr RepoFinderResult))
result <- (Ptr (Ptr GError) -> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult)))
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> (Ptr (Ptr GError)
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult)))
forall a b. (a -> b) -> a -> b
$ Ptr RepoFinder
-> Ptr AsyncResult
-> Ptr (Ptr GError)
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult)))
ostree_repo_finder_resolve_finish Ptr RepoFinder
self' Ptr AsyncResult
result_'
Text -> Ptr (GPtrArray (Ptr RepoFinderResult)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"repoFinderResolveFinish" Ptr (GPtrArray (Ptr RepoFinderResult))
result
[Ptr RepoFinderResult]
result' <- Ptr (GPtrArray (Ptr RepoFinderResult)) -> IO [Ptr RepoFinderResult]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr RepoFinderResult))
result
[RepoFinderResult]
result'' <- (Ptr RepoFinderResult -> IO RepoFinderResult)
-> [Ptr RepoFinderResult] -> IO [RepoFinderResult]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr RepoFinderResult -> RepoFinderResult)
-> Ptr RepoFinderResult -> IO RepoFinderResult
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RepoFinderResult -> RepoFinderResult
OSTree.RepoFinderResult.RepoFinderResult) [Ptr RepoFinderResult]
result'
Ptr (GPtrArray (Ptr RepoFinderResult)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr RepoFinderResult))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
[RepoFinderResult] -> IO [RepoFinderResult]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [RepoFinderResult]
result''
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data RepoFinderResolveFinishMethodInfo
instance (signature ~ (b -> m [OSTree.RepoFinderResult.RepoFinderResult]), MonadIO m, IsRepoFinder a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod RepoFinderResolveFinishMethodInfo a signature where
overloadedMethod = repoFinderResolveFinish
instance O.OverloadedMethodInfo RepoFinderResolveFinishMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.OSTree.Interfaces.RepoFinder.repoFinderResolveFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.19/docs/GI-OSTree-Interfaces-RepoFinder.html#v:repoFinderResolveFinish"
})
#endif
foreign import ccall "ostree_repo_finder_resolve_all_async" ostree_repo_finder_resolve_all_async ::
Ptr (Ptr RepoFinder) ->
Ptr (Ptr OSTree.CollectionRef.CollectionRef) ->
Ptr OSTree.Repo.Repo ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
repoFinderResolveAllAsync ::
(B.CallStack.HasCallStack, MonadIO m, OSTree.Repo.IsRepo a, Gio.Cancellable.IsCancellable b) =>
[RepoFinder]
-> [OSTree.CollectionRef.CollectionRef]
-> a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
repoFinderResolveAllAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRepo a, IsCancellable b) =>
[RepoFinder]
-> [CollectionRef]
-> a
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
repoFinderResolveAllAsync [RepoFinder]
finders [CollectionRef]
refs a
parentRepo Maybe b
cancellable Maybe AsyncReadyCallback
callback = 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 RepoFinder]
finders' <- (RepoFinder -> IO (Ptr RepoFinder))
-> [RepoFinder] -> IO [Ptr RepoFinder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM RepoFinder -> IO (Ptr RepoFinder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [RepoFinder]
finders
Ptr (Ptr RepoFinder)
finders'' <- [Ptr RepoFinder] -> IO (Ptr (Ptr RepoFinder))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packZeroTerminatedPtrArray [Ptr RepoFinder]
finders'
[Ptr CollectionRef]
refs' <- (CollectionRef -> IO (Ptr CollectionRef))
-> [CollectionRef] -> IO [Ptr CollectionRef]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM CollectionRef -> IO (Ptr CollectionRef)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [CollectionRef]
refs
Ptr (Ptr CollectionRef)
refs'' <- [Ptr CollectionRef] -> IO (Ptr (Ptr CollectionRef))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packZeroTerminatedPtrArray [Ptr CollectionRef]
refs'
Ptr Repo
parentRepo' <- a -> IO (Ptr Repo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
parentRepo
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr (Ptr RepoFinder)
-> Ptr (Ptr CollectionRef)
-> Ptr Repo
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
ostree_repo_finder_resolve_all_async Ptr (Ptr RepoFinder)
finders'' Ptr (Ptr CollectionRef)
refs'' Ptr Repo
parentRepo' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
(RepoFinder -> IO ()) -> [RepoFinder] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ RepoFinder -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [RepoFinder]
finders
(CollectionRef -> IO ()) -> [CollectionRef] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CollectionRef -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [CollectionRef]
refs
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
parentRepo
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr (Ptr RepoFinder) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr RepoFinder)
finders''
Ptr (Ptr CollectionRef) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CollectionRef)
refs''
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "ostree_repo_finder_resolve_all_finish" ostree_repo_finder_resolve_all_finish ::
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr (GPtrArray (Ptr OSTree.RepoFinderResult.RepoFinderResult)))
repoFinderResolveAllFinish ::
(B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
a
-> m [OSTree.RepoFinderResult.RepoFinderResult]
repoFinderResolveAllFinish :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAsyncResult a) =>
a -> m [RepoFinderResult]
repoFinderResolveAllFinish a
result_ = IO [RepoFinderResult] -> m [RepoFinderResult]
forall a. IO a -> m a
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 AsyncResult
result_' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
result_
IO [RepoFinderResult] -> IO () -> IO [RepoFinderResult]
forall a b. IO a -> IO b -> IO a
onException (do
Ptr (GPtrArray (Ptr RepoFinderResult))
result <- (Ptr (Ptr GError) -> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult)))
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> (Ptr (Ptr GError)
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult))))
-> IO (Ptr (GPtrArray (Ptr RepoFinderResult)))
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult
-> Ptr (Ptr GError) -> IO (Ptr (GPtrArray (Ptr RepoFinderResult)))
ostree_repo_finder_resolve_all_finish Ptr AsyncResult
result_'
Text -> Ptr (GPtrArray (Ptr RepoFinderResult)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"repoFinderResolveAllFinish" Ptr (GPtrArray (Ptr RepoFinderResult))
result
[Ptr RepoFinderResult]
result' <- Ptr (GPtrArray (Ptr RepoFinderResult)) -> IO [Ptr RepoFinderResult]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr RepoFinderResult))
result
[RepoFinderResult]
result'' <- (Ptr RepoFinderResult -> IO RepoFinderResult)
-> [Ptr RepoFinderResult] -> IO [RepoFinderResult]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr RepoFinderResult -> RepoFinderResult)
-> Ptr RepoFinderResult -> IO RepoFinderResult
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RepoFinderResult -> RepoFinderResult
OSTree.RepoFinderResult.RepoFinderResult) [Ptr RepoFinderResult]
result'
Ptr (GPtrArray (Ptr RepoFinderResult)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr RepoFinderResult))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
result_
[RepoFinderResult] -> IO [RepoFinderResult]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [RepoFinderResult]
result''
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList RepoFinder = RepoFinderSignalList
type RepoFinderSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif