{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.AsyncQueue
    ( 
    AsyncQueue(..)                          ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveAsyncQueueMethod                 ,
#endif
#if defined(ENABLE_OVERLOADING)
    AsyncQueueLengthMethodInfo              ,
#endif
    asyncQueueLength                        ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueLengthUnlockedMethodInfo      ,
#endif
    asyncQueueLengthUnlocked                ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueLockMethodInfo                ,
#endif
    asyncQueueLock                          ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePopMethodInfo                 ,
#endif
    asyncQueuePop                           ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePopUnlockedMethodInfo         ,
#endif
    asyncQueuePopUnlocked                   ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushMethodInfo                ,
#endif
    asyncQueuePush                          ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushFrontMethodInfo           ,
#endif
    asyncQueuePushFront                     ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushFrontUnlockedMethodInfo   ,
#endif
    asyncQueuePushFrontUnlocked             ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushSortedMethodInfo          ,
#endif
    asyncQueuePushSorted                    ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushSortedUnlockedMethodInfo  ,
#endif
    asyncQueuePushSortedUnlocked            ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushUnlockedMethodInfo        ,
#endif
    asyncQueuePushUnlocked                  ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueRefUnlockedMethodInfo         ,
#endif
    asyncQueueRefUnlocked                   ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueRemoveMethodInfo              ,
#endif
    asyncQueueRemove                        ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueRemoveUnlockedMethodInfo      ,
#endif
    asyncQueueRemoveUnlocked                ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueSortMethodInfo                ,
#endif
    asyncQueueSort                          ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueSortUnlockedMethodInfo        ,
#endif
    asyncQueueSortUnlocked                  ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimedPopMethodInfo            ,
#endif
    asyncQueueTimedPop                      ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimedPopUnlockedMethodInfo    ,
#endif
    asyncQueueTimedPopUnlocked              ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimeoutPopMethodInfo          ,
#endif
    asyncQueueTimeoutPop                    ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimeoutPopUnlockedMethodInfo  ,
#endif
    asyncQueueTimeoutPopUnlocked            ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueTryPopMethodInfo              ,
#endif
    asyncQueueTryPop                        ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueTryPopUnlockedMethodInfo      ,
#endif
    asyncQueueTryPopUnlocked                ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueUnlockMethodInfo              ,
#endif
    asyncQueueUnlock                        ,
#if defined(ENABLE_OVERLOADING)
    AsyncQueueUnrefAndUnlockMethodInfo      ,
#endif
    asyncQueueUnrefAndUnlock                ,
    ) 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 {-# SOURCE #-} qualified GI.GLib.Structs.TimeVal as GLib.TimeVal
#else
import qualified GI.GLib.Callbacks as GLib.Callbacks
import {-# SOURCE #-} qualified GI.GLib.Structs.TimeVal as GLib.TimeVal
#endif
newtype AsyncQueue = AsyncQueue (SP.ManagedPtr AsyncQueue)
    deriving (AsyncQueue -> AsyncQueue -> Bool
(AsyncQueue -> AsyncQueue -> Bool)
-> (AsyncQueue -> AsyncQueue -> Bool) -> Eq AsyncQueue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AsyncQueue -> AsyncQueue -> Bool
== :: AsyncQueue -> AsyncQueue -> Bool
$c/= :: AsyncQueue -> AsyncQueue -> Bool
/= :: AsyncQueue -> AsyncQueue -> Bool
Eq)
instance SP.ManagedPtrNewtype AsyncQueue where
    toManagedPtr :: AsyncQueue -> ManagedPtr AsyncQueue
toManagedPtr (AsyncQueue ManagedPtr AsyncQueue
p) = ManagedPtr AsyncQueue
p
instance BoxedPtr AsyncQueue where
    boxedPtrCopy :: AsyncQueue -> IO AsyncQueue
boxedPtrCopy = AsyncQueue -> IO AsyncQueue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: AsyncQueue -> IO ()
boxedPtrFree = \AsyncQueue
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AsyncQueue
type instance O.AttributeList AsyncQueue = AsyncQueueAttributeList
type AsyncQueueAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "g_async_queue_length" g_async_queue_length :: 
    Ptr AsyncQueue ->                       
    IO Int32
asyncQueueLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m Int32
    
asyncQueueLength :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m Int32
asyncQueueLength AsyncQueue
queue = IO Int32 -> m Int32
forall a. IO a -> m a
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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Int32
result <- Ptr AsyncQueue -> IO Int32
g_async_queue_length Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueLengthMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod AsyncQueueLengthMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueLength
instance O.OverloadedMethodInfo AsyncQueueLengthMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueLength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueLength"
        })
#endif
foreign import ccall "g_async_queue_length_unlocked" g_async_queue_length_unlocked :: 
    Ptr AsyncQueue ->                       
    IO Int32
asyncQueueLengthUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m Int32
    
asyncQueueLengthUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m Int32
asyncQueueLengthUnlocked AsyncQueue
queue = IO Int32 -> m Int32
forall a. IO a -> m a
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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Int32
result <- Ptr AsyncQueue -> IO Int32
g_async_queue_length_unlocked Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueLengthUnlockedMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod AsyncQueueLengthUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueLengthUnlocked
instance O.OverloadedMethodInfo AsyncQueueLengthUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueLengthUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueLengthUnlocked"
        })
#endif
foreign import ccall "g_async_queue_lock" g_async_queue_lock :: 
    Ptr AsyncQueue ->                       
    IO ()
asyncQueueLock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m ()
asyncQueueLock :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m ()
asyncQueueLock AsyncQueue
queue = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> IO ()
g_async_queue_lock Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueueLockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AsyncQueueLockMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueLock
instance O.OverloadedMethodInfo AsyncQueueLockMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueLock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueLock"
        })
#endif
foreign import ccall "g_async_queue_pop" g_async_queue_pop :: 
    Ptr AsyncQueue ->                       
    IO (Ptr ())
asyncQueuePop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m (Ptr ())
    
asyncQueuePop :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m (Ptr ())
asyncQueuePop AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr ()
result <- Ptr AsyncQueue -> IO (Ptr ())
g_async_queue_pop Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePopMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueuePopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePop
instance O.OverloadedMethodInfo AsyncQueuePopMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePop"
        })
#endif
foreign import ccall "g_async_queue_pop_unlocked" g_async_queue_pop_unlocked :: 
    Ptr AsyncQueue ->                       
    IO (Ptr ())
asyncQueuePopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m (Ptr ())
    
asyncQueuePopUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m (Ptr ())
asyncQueuePopUnlocked AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr ()
result <- Ptr AsyncQueue -> IO (Ptr ())
g_async_queue_pop_unlocked Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePopUnlockedMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueuePopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePopUnlocked
instance O.OverloadedMethodInfo AsyncQueuePopUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePopUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePopUnlocked"
        })
#endif
foreign import ccall "g_async_queue_push" g_async_queue_push :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    IO ()
asyncQueuePush ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> m ()
asyncQueuePush :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> m ()
asyncQueuePush AsyncQueue
queue Ptr ()
data_ = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> Ptr () -> IO ()
g_async_queue_push Ptr AsyncQueue
queue' Ptr ()
data_
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueuePushMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePush
instance O.OverloadedMethodInfo AsyncQueuePushMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePush",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePush"
        })
#endif
foreign import ccall "g_async_queue_push_front" g_async_queue_push_front :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    IO ()
asyncQueuePushFront ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> m ()
asyncQueuePushFront :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> m ()
asyncQueuePushFront AsyncQueue
queue Ptr ()
item = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> Ptr () -> IO ()
g_async_queue_push_front Ptr AsyncQueue
queue' Ptr ()
item
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushFrontMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueuePushFrontMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushFront
instance O.OverloadedMethodInfo AsyncQueuePushFrontMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePushFront",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePushFront"
        })
#endif
foreign import ccall "g_async_queue_push_front_unlocked" g_async_queue_push_front_unlocked :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    IO ()
asyncQueuePushFrontUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> m ()
asyncQueuePushFrontUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> m ()
asyncQueuePushFrontUnlocked AsyncQueue
queue Ptr ()
item = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> Ptr () -> IO ()
g_async_queue_push_front_unlocked Ptr AsyncQueue
queue' Ptr ()
item
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushFrontUnlockedMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueuePushFrontUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushFrontUnlocked
instance O.OverloadedMethodInfo AsyncQueuePushFrontUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePushFrontUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePushFrontUnlocked"
        })
#endif
foreign import ccall "g_async_queue_push_sorted" g_async_queue_push_sorted :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    FunPtr GLib.Callbacks.C_CompareDataFunc -> 
    Ptr () ->                               
    IO ()
asyncQueuePushSorted ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> GLib.Callbacks.CompareDataFunc
    
    -> m ()
asyncQueuePushSorted :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> CompareDataFunc -> m ()
asyncQueuePushSorted AsyncQueue
queue Ptr ()
data_ CompareDataFunc
func = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    FunPtr C_CompareDataFunc
func' <- C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
GLib.Callbacks.mk_CompareDataFunc (Maybe (Ptr (FunPtr C_CompareDataFunc))
-> C_CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.wrap_CompareDataFunc Maybe (Ptr (FunPtr C_CompareDataFunc))
forall a. Maybe a
Nothing (CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.drop_closures_CompareDataFunc CompareDataFunc
func))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr AsyncQueue
-> Ptr () -> FunPtr C_CompareDataFunc -> Ptr () -> IO ()
g_async_queue_push_sorted Ptr AsyncQueue
queue' Ptr ()
data_ FunPtr C_CompareDataFunc
func' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_CompareDataFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_CompareDataFunc
func'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushSortedMethodInfo
instance (signature ~ (Ptr () -> GLib.Callbacks.CompareDataFunc -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueuePushSortedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushSorted
instance O.OverloadedMethodInfo AsyncQueuePushSortedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePushSorted",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePushSorted"
        })
#endif
foreign import ccall "g_async_queue_push_sorted_unlocked" g_async_queue_push_sorted_unlocked :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    FunPtr GLib.Callbacks.C_CompareDataFunc -> 
    Ptr () ->                               
    IO ()
asyncQueuePushSortedUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> GLib.Callbacks.CompareDataFunc
    
    -> m ()
asyncQueuePushSortedUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> CompareDataFunc -> m ()
asyncQueuePushSortedUnlocked AsyncQueue
queue Ptr ()
data_ CompareDataFunc
func = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    FunPtr C_CompareDataFunc
func' <- C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
GLib.Callbacks.mk_CompareDataFunc (Maybe (Ptr (FunPtr C_CompareDataFunc))
-> C_CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.wrap_CompareDataFunc Maybe (Ptr (FunPtr C_CompareDataFunc))
forall a. Maybe a
Nothing (CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.drop_closures_CompareDataFunc CompareDataFunc
func))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr AsyncQueue
-> Ptr () -> FunPtr C_CompareDataFunc -> Ptr () -> IO ()
g_async_queue_push_sorted_unlocked Ptr AsyncQueue
queue' Ptr ()
data_ FunPtr C_CompareDataFunc
func' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_CompareDataFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_CompareDataFunc
func'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushSortedUnlockedMethodInfo
instance (signature ~ (Ptr () -> GLib.Callbacks.CompareDataFunc -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueuePushSortedUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushSortedUnlocked
instance O.OverloadedMethodInfo AsyncQueuePushSortedUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePushSortedUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePushSortedUnlocked"
        })
#endif
foreign import ccall "g_async_queue_push_unlocked" g_async_queue_push_unlocked :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    IO ()
asyncQueuePushUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> m ()
asyncQueuePushUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> m ()
asyncQueuePushUnlocked AsyncQueue
queue Ptr ()
data_ = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> Ptr () -> IO ()
g_async_queue_push_unlocked Ptr AsyncQueue
queue' Ptr ()
data_
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushUnlockedMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueuePushUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushUnlocked
instance O.OverloadedMethodInfo AsyncQueuePushUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueuePushUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueuePushUnlocked"
        })
#endif
foreign import ccall "g_async_queue_ref_unlocked" g_async_queue_ref_unlocked :: 
    Ptr AsyncQueue ->                       
    IO ()
{-# DEPRECATED asyncQueueRefUnlocked ["(Since version 2.8)","Reference counting is done atomically.","so @/g_async_queue_ref()/@ can be used regardless of the /@queue@/\\'s","lock."] #-}
asyncQueueRefUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m ()
asyncQueueRefUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m ()
asyncQueueRefUnlocked AsyncQueue
queue = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> IO ()
g_async_queue_ref_unlocked Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueueRefUnlockedMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AsyncQueueRefUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueRefUnlocked
instance O.OverloadedMethodInfo AsyncQueueRefUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueRefUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueRefUnlocked"
        })
#endif
foreign import ccall "g_async_queue_remove" g_async_queue_remove :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    IO CInt
asyncQueueRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> m Bool
    
asyncQueueRemove :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> m Bool
asyncQueueRemove AsyncQueue
queue Ptr ()
item = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    CInt
result <- Ptr AsyncQueue -> Ptr () -> IO CInt
g_async_queue_remove Ptr AsyncQueue
queue' Ptr ()
item
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data AsyncQueueRemoveMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.OverloadedMethod AsyncQueueRemoveMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueRemove
instance O.OverloadedMethodInfo AsyncQueueRemoveMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueRemove"
        })
#endif
foreign import ccall "g_async_queue_remove_unlocked" g_async_queue_remove_unlocked :: 
    Ptr AsyncQueue ->                       
    Ptr () ->                               
    IO CInt
asyncQueueRemoveUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Ptr ()
    
    -> m Bool
    
asyncQueueRemoveUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Ptr () -> m Bool
asyncQueueRemoveUnlocked AsyncQueue
queue Ptr ()
item = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    CInt
result <- Ptr AsyncQueue -> Ptr () -> IO CInt
g_async_queue_remove_unlocked Ptr AsyncQueue
queue' Ptr ()
item
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data AsyncQueueRemoveUnlockedMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.OverloadedMethod AsyncQueueRemoveUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueRemoveUnlocked
instance O.OverloadedMethodInfo AsyncQueueRemoveUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueRemoveUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueRemoveUnlocked"
        })
#endif
foreign import ccall "g_async_queue_sort" g_async_queue_sort :: 
    Ptr AsyncQueue ->                       
    FunPtr GLib.Callbacks.C_CompareDataFunc -> 
    Ptr () ->                               
    IO ()
asyncQueueSort ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> GLib.Callbacks.CompareDataFunc
    
    -> m ()
asyncQueueSort :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> CompareDataFunc -> m ()
asyncQueueSort AsyncQueue
queue CompareDataFunc
func = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    FunPtr C_CompareDataFunc
func' <- C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
GLib.Callbacks.mk_CompareDataFunc (Maybe (Ptr (FunPtr C_CompareDataFunc))
-> C_CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.wrap_CompareDataFunc Maybe (Ptr (FunPtr C_CompareDataFunc))
forall a. Maybe a
Nothing (CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.drop_closures_CompareDataFunc CompareDataFunc
func))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr AsyncQueue -> FunPtr C_CompareDataFunc -> Ptr () -> IO ()
g_async_queue_sort Ptr AsyncQueue
queue' FunPtr C_CompareDataFunc
func' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_CompareDataFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_CompareDataFunc
func'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueueSortMethodInfo
instance (signature ~ (GLib.Callbacks.CompareDataFunc -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueueSortMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueSort
instance O.OverloadedMethodInfo AsyncQueueSortMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueSort",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueSort"
        })
#endif
foreign import ccall "g_async_queue_sort_unlocked" g_async_queue_sort_unlocked :: 
    Ptr AsyncQueue ->                       
    FunPtr GLib.Callbacks.C_CompareDataFunc -> 
    Ptr () ->                               
    IO ()
asyncQueueSortUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> GLib.Callbacks.CompareDataFunc
    
    -> m ()
asyncQueueSortUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> CompareDataFunc -> m ()
asyncQueueSortUnlocked AsyncQueue
queue CompareDataFunc
func = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    FunPtr C_CompareDataFunc
func' <- C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
GLib.Callbacks.mk_CompareDataFunc (Maybe (Ptr (FunPtr C_CompareDataFunc))
-> C_CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.wrap_CompareDataFunc Maybe (Ptr (FunPtr C_CompareDataFunc))
forall a. Maybe a
Nothing (CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.drop_closures_CompareDataFunc CompareDataFunc
func))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr AsyncQueue -> FunPtr C_CompareDataFunc -> Ptr () -> IO ()
g_async_queue_sort_unlocked Ptr AsyncQueue
queue' FunPtr C_CompareDataFunc
func' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_CompareDataFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_CompareDataFunc
func'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueueSortUnlockedMethodInfo
instance (signature ~ (GLib.Callbacks.CompareDataFunc -> m ()), MonadIO m) => O.OverloadedMethod AsyncQueueSortUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueSortUnlocked
instance O.OverloadedMethodInfo AsyncQueueSortUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueSortUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueSortUnlocked"
        })
#endif
foreign import ccall "g_async_queue_timed_pop" g_async_queue_timed_pop :: 
    Ptr AsyncQueue ->                       
    Ptr GLib.TimeVal.TimeVal ->             
    IO (Ptr ())
{-# DEPRECATED asyncQueueTimedPop ["use 'GI.GLib.Structs.AsyncQueue.asyncQueueTimeoutPop'."] #-}
asyncQueueTimedPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> GLib.TimeVal.TimeVal
    
    -> m (Ptr ())
    
    
asyncQueueTimedPop :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> TimeVal -> m (Ptr ())
asyncQueueTimedPop AsyncQueue
queue TimeVal
endTime = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr TimeVal
endTime' <- TimeVal -> IO (Ptr TimeVal)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TimeVal
endTime
    Ptr ()
result <- Ptr AsyncQueue -> Ptr TimeVal -> IO (Ptr ())
g_async_queue_timed_pop Ptr AsyncQueue
queue' Ptr TimeVal
endTime'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    TimeVal -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TimeVal
endTime
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueTimedPopMethodInfo
instance (signature ~ (GLib.TimeVal.TimeVal -> m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueueTimedPopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimedPop
instance O.OverloadedMethodInfo AsyncQueueTimedPopMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueTimedPop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueTimedPop"
        })
#endif
foreign import ccall "g_async_queue_timed_pop_unlocked" g_async_queue_timed_pop_unlocked :: 
    Ptr AsyncQueue ->                       
    Ptr GLib.TimeVal.TimeVal ->             
    IO (Ptr ())
{-# DEPRECATED asyncQueueTimedPopUnlocked ["use 'GI.GLib.Structs.AsyncQueue.asyncQueueTimeoutPopUnlocked'."] #-}
asyncQueueTimedPopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> GLib.TimeVal.TimeVal
    
    -> m (Ptr ())
    
    
asyncQueueTimedPopUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> TimeVal -> m (Ptr ())
asyncQueueTimedPopUnlocked AsyncQueue
queue TimeVal
endTime = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr TimeVal
endTime' <- TimeVal -> IO (Ptr TimeVal)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TimeVal
endTime
    Ptr ()
result <- Ptr AsyncQueue -> Ptr TimeVal -> IO (Ptr ())
g_async_queue_timed_pop_unlocked Ptr AsyncQueue
queue' Ptr TimeVal
endTime'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    TimeVal -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TimeVal
endTime
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueTimedPopUnlockedMethodInfo
instance (signature ~ (GLib.TimeVal.TimeVal -> m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueueTimedPopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimedPopUnlocked
instance O.OverloadedMethodInfo AsyncQueueTimedPopUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueTimedPopUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueTimedPopUnlocked"
        })
#endif
foreign import ccall "g_async_queue_timeout_pop" g_async_queue_timeout_pop :: 
    Ptr AsyncQueue ->                       
    Word64 ->                               
    IO (Ptr ())
asyncQueueTimeoutPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Word64
    
    -> m (Ptr ())
    
    
asyncQueueTimeoutPop :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Word64 -> m (Ptr ())
asyncQueueTimeoutPop AsyncQueue
queue Word64
timeout = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr ()
result <- Ptr AsyncQueue -> Word64 -> IO (Ptr ())
g_async_queue_timeout_pop Ptr AsyncQueue
queue' Word64
timeout
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueTimeoutPopMethodInfo
instance (signature ~ (Word64 -> m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueueTimeoutPopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimeoutPop
instance O.OverloadedMethodInfo AsyncQueueTimeoutPopMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueTimeoutPop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueTimeoutPop"
        })
#endif
foreign import ccall "g_async_queue_timeout_pop_unlocked" g_async_queue_timeout_pop_unlocked :: 
    Ptr AsyncQueue ->                       
    Word64 ->                               
    IO (Ptr ())
asyncQueueTimeoutPopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> Word64
    
    -> m (Ptr ())
    
    
asyncQueueTimeoutPopUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> Word64 -> m (Ptr ())
asyncQueueTimeoutPopUnlocked AsyncQueue
queue Word64
timeout = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr ()
result <- Ptr AsyncQueue -> Word64 -> IO (Ptr ())
g_async_queue_timeout_pop_unlocked Ptr AsyncQueue
queue' Word64
timeout
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueTimeoutPopUnlockedMethodInfo
instance (signature ~ (Word64 -> m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueueTimeoutPopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimeoutPopUnlocked
instance O.OverloadedMethodInfo AsyncQueueTimeoutPopUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueTimeoutPopUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueTimeoutPopUnlocked"
        })
#endif
foreign import ccall "g_async_queue_try_pop" g_async_queue_try_pop :: 
    Ptr AsyncQueue ->                       
    IO (Ptr ())
asyncQueueTryPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m (Ptr ())
    
    
asyncQueueTryPop :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m (Ptr ())
asyncQueueTryPop AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr ()
result <- Ptr AsyncQueue -> IO (Ptr ())
g_async_queue_try_pop Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueTryPopMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueueTryPopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTryPop
instance O.OverloadedMethodInfo AsyncQueueTryPopMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueTryPop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueTryPop"
        })
#endif
foreign import ccall "g_async_queue_try_pop_unlocked" g_async_queue_try_pop_unlocked :: 
    Ptr AsyncQueue ->                       
    IO (Ptr ())
asyncQueueTryPopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m (Ptr ())
    
    
asyncQueueTryPopUnlocked :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m (Ptr ())
asyncQueueTryPopUnlocked AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr ()
result <- Ptr AsyncQueue -> IO (Ptr ())
g_async_queue_try_pop_unlocked Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data AsyncQueueTryPopUnlockedMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.OverloadedMethod AsyncQueueTryPopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTryPopUnlocked
instance O.OverloadedMethodInfo AsyncQueueTryPopUnlockedMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueTryPopUnlocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueTryPopUnlocked"
        })
#endif
foreign import ccall "g_async_queue_unlock" g_async_queue_unlock :: 
    Ptr AsyncQueue ->                       
    IO ()
asyncQueueUnlock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m ()
asyncQueueUnlock :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m ()
asyncQueueUnlock AsyncQueue
queue = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> IO ()
g_async_queue_unlock Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueueUnlockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AsyncQueueUnlockMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueUnlock
instance O.OverloadedMethodInfo AsyncQueueUnlockMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueUnlock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueUnlock"
        })
#endif
foreign import ccall "g_async_queue_unref_and_unlock" g_async_queue_unref_and_unlock :: 
    Ptr AsyncQueue ->                       
    IO ()
{-# DEPRECATED asyncQueueUnrefAndUnlock ["(Since version 2.8)","Reference counting is done atomically.","so 'GI.GLib.Structs.AsyncQueue.asyncQueueUnref' can be used regardless of the /@queue@/\\'s","lock."] #-}
asyncQueueUnrefAndUnlock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    
    -> m ()
asyncQueueUnrefAndUnlock :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AsyncQueue -> m ()
asyncQueueUnrefAndUnlock AsyncQueue
queue = 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 AsyncQueue
queue' <- AsyncQueue -> IO (Ptr AsyncQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AsyncQueue
queue
    Ptr AsyncQueue -> IO ()
g_async_queue_unref_and_unlock Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AsyncQueueUnrefAndUnlockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AsyncQueueUnrefAndUnlockMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueUnrefAndUnlock
instance O.OverloadedMethodInfo AsyncQueueUnrefAndUnlockMethodInfo AsyncQueue where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.AsyncQueue.asyncQueueUnrefAndUnlock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-AsyncQueue.html#v:asyncQueueUnrefAndUnlock"
        })
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAsyncQueueMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveAsyncQueueMethod "length" o = AsyncQueueLengthMethodInfo
    ResolveAsyncQueueMethod "lengthUnlocked" o = AsyncQueueLengthUnlockedMethodInfo
    ResolveAsyncQueueMethod "lock" o = AsyncQueueLockMethodInfo
    ResolveAsyncQueueMethod "pop" o = AsyncQueuePopMethodInfo
    ResolveAsyncQueueMethod "popUnlocked" o = AsyncQueuePopUnlockedMethodInfo
    ResolveAsyncQueueMethod "push" o = AsyncQueuePushMethodInfo
    ResolveAsyncQueueMethod "pushFront" o = AsyncQueuePushFrontMethodInfo
    ResolveAsyncQueueMethod "pushFrontUnlocked" o = AsyncQueuePushFrontUnlockedMethodInfo
    ResolveAsyncQueueMethod "pushSorted" o = AsyncQueuePushSortedMethodInfo
    ResolveAsyncQueueMethod "pushSortedUnlocked" o = AsyncQueuePushSortedUnlockedMethodInfo
    ResolveAsyncQueueMethod "pushUnlocked" o = AsyncQueuePushUnlockedMethodInfo
    ResolveAsyncQueueMethod "refUnlocked" o = AsyncQueueRefUnlockedMethodInfo
    ResolveAsyncQueueMethod "remove" o = AsyncQueueRemoveMethodInfo
    ResolveAsyncQueueMethod "removeUnlocked" o = AsyncQueueRemoveUnlockedMethodInfo
    ResolveAsyncQueueMethod "sort" o = AsyncQueueSortMethodInfo
    ResolveAsyncQueueMethod "sortUnlocked" o = AsyncQueueSortUnlockedMethodInfo
    ResolveAsyncQueueMethod "timedPop" o = AsyncQueueTimedPopMethodInfo
    ResolveAsyncQueueMethod "timedPopUnlocked" o = AsyncQueueTimedPopUnlockedMethodInfo
    ResolveAsyncQueueMethod "timeoutPop" o = AsyncQueueTimeoutPopMethodInfo
    ResolveAsyncQueueMethod "timeoutPopUnlocked" o = AsyncQueueTimeoutPopUnlockedMethodInfo
    ResolveAsyncQueueMethod "tryPop" o = AsyncQueueTryPopMethodInfo
    ResolveAsyncQueueMethod "tryPopUnlocked" o = AsyncQueueTryPopUnlockedMethodInfo
    ResolveAsyncQueueMethod "unlock" o = AsyncQueueUnlockMethodInfo
    ResolveAsyncQueueMethod "unrefAndUnlock" o = AsyncQueueUnrefAndUnlockMethodInfo
    ResolveAsyncQueueMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAsyncQueueMethod t AsyncQueue, O.OverloadedMethod info AsyncQueue p) => OL.IsLabel t (AsyncQueue -> 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 ~ ResolveAsyncQueueMethod t AsyncQueue, O.OverloadedMethod info AsyncQueue p, R.HasField t AsyncQueue p) => R.HasField t AsyncQueue p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAsyncQueueMethod t AsyncQueue, O.OverloadedMethodInfo info AsyncQueue) => OL.IsLabel t (O.MethodProxy info AsyncQueue) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif