{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GAsyncQueue struct is an opaque data structure which represents
-- an asynchronous queue. It should only be accessed through the
-- g_async_queue_* functions.

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

module GI.GLib.Structs.AsyncQueue
    ( 

-- * Exported types
    AsyncQueue(..)                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAsyncQueueMethod                 ,
#endif


-- ** length #method:length#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueLengthMethodInfo              ,
#endif
    asyncQueueLength                        ,


-- ** lengthUnlocked #method:lengthUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueLengthUnlockedMethodInfo      ,
#endif
    asyncQueueLengthUnlocked                ,


-- ** lock #method:lock#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueLockMethodInfo                ,
#endif
    asyncQueueLock                          ,


-- ** pop #method:pop#

#if defined(ENABLE_OVERLOADING)
    AsyncQueuePopMethodInfo                 ,
#endif
    asyncQueuePop                           ,


-- ** popUnlocked #method:popUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueuePopUnlockedMethodInfo         ,
#endif
    asyncQueuePopUnlocked                   ,


-- ** push #method:push#

#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushMethodInfo                ,
#endif
    asyncQueuePush                          ,


-- ** pushFront #method:pushFront#

#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushFrontMethodInfo           ,
#endif
    asyncQueuePushFront                     ,


-- ** pushFrontUnlocked #method:pushFrontUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushFrontUnlockedMethodInfo   ,
#endif
    asyncQueuePushFrontUnlocked             ,


-- ** pushUnlocked #method:pushUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueuePushUnlockedMethodInfo        ,
#endif
    asyncQueuePushUnlocked                  ,


-- ** refUnlocked #method:refUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueRefUnlockedMethodInfo         ,
#endif
    asyncQueueRefUnlocked                   ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueRemoveMethodInfo              ,
#endif
    asyncQueueRemove                        ,


-- ** removeUnlocked #method:removeUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueRemoveUnlockedMethodInfo      ,
#endif
    asyncQueueRemoveUnlocked                ,


-- ** timedPop #method:timedPop#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimedPopMethodInfo            ,
#endif
    asyncQueueTimedPop                      ,


-- ** timedPopUnlocked #method:timedPopUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimedPopUnlockedMethodInfo    ,
#endif
    asyncQueueTimedPopUnlocked              ,


-- ** timeoutPop #method:timeoutPop#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimeoutPopMethodInfo          ,
#endif
    asyncQueueTimeoutPop                    ,


-- ** timeoutPopUnlocked #method:timeoutPopUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueTimeoutPopUnlockedMethodInfo  ,
#endif
    asyncQueueTimeoutPopUnlocked            ,


-- ** tryPop #method:tryPop#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueTryPopMethodInfo              ,
#endif
    asyncQueueTryPop                        ,


-- ** tryPopUnlocked #method:tryPopUnlocked#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueTryPopUnlockedMethodInfo      ,
#endif
    asyncQueueTryPopUnlocked                ,


-- ** unlock #method:unlock#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueUnlockMethodInfo              ,
#endif
    asyncQueueUnlock                        ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    AsyncQueueUnrefMethodInfo               ,
#endif
    asyncQueueUnref                         ,


-- ** unrefAndUnlock #method:unrefAndUnlock#

#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.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.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 {-# SOURCE #-} qualified GI.GLib.Structs.TimeVal as GLib.TimeVal

-- | Memory-managed wrapper type.
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
/= :: AsyncQueue -> AsyncQueue -> Bool
$c/= :: AsyncQueue -> AsyncQueue -> Bool
== :: AsyncQueue -> AsyncQueue -> Bool
$c== :: AsyncQueue -> AsyncQueue -> Bool
Eq)

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

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr AsyncQueue where
    boxedPtrCopy :: AsyncQueue -> IO AsyncQueue
boxedPtrCopy = AsyncQueue -> IO AsyncQueue
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: AsyncQueue -> IO ()
boxedPtrFree = \AsyncQueue
_x -> () -> IO ()
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, *)])
#endif

-- method AsyncQueue::length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue." , 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 "g_async_queue_length" g_async_queue_length :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO Int32

-- | Returns the length of the queue.
-- 
-- Actually this function returns the number of data items in
-- the queue minus the number of waiting threads, so a negative
-- value means waiting threads, and a positive value means available
-- entries in the /@queue@/. A return value of 0 could mean n entries
-- in the queue and n threads waiting. This can happen due to locking
-- of the queue or due to scheduling.
asyncQueueLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'.
    -> m Int32
    -- ^ __Returns:__ the length of the /@queue@/
asyncQueueLength :: AsyncQueue -> m Int32
asyncQueueLength AsyncQueue
queue = 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 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 (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueueLengthMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo AsyncQueueLengthMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueLength

#endif

-- method AsyncQueue::length_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , 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 "g_async_queue_length_unlocked" g_async_queue_length_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO Int32

-- | Returns the length of the queue.
-- 
-- Actually this function returns the number of data items in
-- the queue minus the number of waiting threads, so a negative
-- value means waiting threads, and a positive value means available
-- entries in the /@queue@/. A return value of 0 could mean n entries
-- in the queue and n threads waiting. This can happen due to locking
-- of the queue or due to scheduling.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
asyncQueueLengthUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m Int32
    -- ^ __Returns:__ the length of the /@queue@/.
asyncQueueLengthUnlocked :: AsyncQueue -> m Int32
asyncQueueLengthUnlocked AsyncQueue
queue = 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 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 (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueueLengthUnlockedMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo AsyncQueueLengthUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueLengthUnlocked

#endif

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

foreign import ccall "g_async_queue_lock" g_async_queue_lock :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO ()

-- | Acquires the /@queue@/\'s lock. If another thread is already
-- holding the lock, this call will block until the lock
-- becomes available.
-- 
-- Call 'GI.GLib.Structs.AsyncQueue.asyncQueueUnlock' to drop the lock again.
-- 
-- While holding the lock, you can only call the
-- g_async_queue_*@/_unlocked()/@ functions on /@queue@/. Otherwise,
-- deadlock may occur.
asyncQueueLock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m ()
asyncQueueLock :: AsyncQueue -> m ()
asyncQueueLock AsyncQueue
queue = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueueLockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AsyncQueueLockMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueLock

#endif

-- method AsyncQueue::pop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_pop" g_async_queue_pop :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO (Ptr ())

-- | Pops data from the /@queue@/. If /@queue@/ is empty, this function
-- blocks until data becomes available.
asyncQueuePop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue
asyncQueuePop :: AsyncQueue -> m (Ptr ())
asyncQueuePop AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
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 (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueuePopMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo AsyncQueuePopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePop

#endif

-- method AsyncQueue::pop_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_pop_unlocked" g_async_queue_pop_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO (Ptr ())

-- | Pops data from the /@queue@/. If /@queue@/ is empty, this function
-- blocks until data becomes available.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
asyncQueuePopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue.
asyncQueuePopUnlocked :: AsyncQueue -> m (Ptr ())
asyncQueuePopUnlocked AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
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 (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueuePopUnlockedMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo AsyncQueuePopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePopUnlocked

#endif

-- method AsyncQueue::push
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "@data to push into the @queue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_push" g_async_queue_push :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO ()

-- | Pushes the /@data@/ into the /@queue@/. /@data@/ must not be 'P.Nothing'.
asyncQueuePush ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Ptr ()
    -- ^ /@data@/: /@data@/ to push into the /@queue@/
    -> m ()
asyncQueuePush :: AsyncQueue -> Ptr () -> m ()
asyncQueuePush AsyncQueue
queue Ptr ()
data_ = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo AsyncQueuePushMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePush

#endif

-- method AsyncQueue::push_front
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to push into the @queue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_push_front" g_async_queue_push_front :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr () ->                               -- item : TBasicType TPtr
    IO ()

-- | Pushes the /@item@/ into the /@queue@/. /@item@/ must not be 'P.Nothing'.
-- In contrast to 'GI.GLib.Structs.AsyncQueue.asyncQueuePush', this function
-- pushes the new item ahead of the items already in the queue,
-- so that it will be the next one to be popped off the queue.
-- 
-- /Since: 2.46/
asyncQueuePushFront ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Ptr ()
    -- ^ /@item@/: data to push into the /@queue@/
    -> m ()
asyncQueuePushFront :: AsyncQueue -> Ptr () -> m ()
asyncQueuePushFront AsyncQueue
queue Ptr ()
item = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushFrontMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo AsyncQueuePushFrontMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushFront

#endif

-- method AsyncQueue::push_front_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to push into the @queue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_push_front_unlocked" g_async_queue_push_front_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr () ->                               -- item : TBasicType TPtr
    IO ()

-- | Pushes the /@item@/ into the /@queue@/. /@item@/ must not be 'P.Nothing'.
-- In contrast to 'GI.GLib.Structs.AsyncQueue.asyncQueuePushUnlocked', this function
-- pushes the new item ahead of the items already in the queue,
-- so that it will be the next one to be popped off the queue.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
-- 
-- /Since: 2.46/
asyncQueuePushFrontUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Ptr ()
    -- ^ /@item@/: data to push into the /@queue@/
    -> m ()
asyncQueuePushFrontUnlocked :: AsyncQueue -> Ptr () -> m ()
asyncQueuePushFrontUnlocked AsyncQueue
queue Ptr ()
item = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushFrontUnlockedMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo AsyncQueuePushFrontUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushFrontUnlocked

#endif

-- method AsyncQueue::push_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "@data to push into the @queue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_push_unlocked" g_async_queue_push_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO ()

-- | Pushes the /@data@/ into the /@queue@/. /@data@/ must not be 'P.Nothing'.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
asyncQueuePushUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Ptr ()
    -- ^ /@data@/: /@data@/ to push into the /@queue@/
    -> m ()
asyncQueuePushUnlocked :: AsyncQueue -> Ptr () -> m ()
asyncQueuePushUnlocked AsyncQueue
queue Ptr ()
data_ = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueuePushUnlockedMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo AsyncQueuePushUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueuePushUnlocked

#endif

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

foreign import ccall "g_async_queue_ref_unlocked" g_async_queue_ref_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "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."] #-}
-- | Increases the reference count of the asynchronous /@queue@/ by 1.
asyncQueueRefUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m ()
asyncQueueRefUnlocked :: AsyncQueue -> m ()
asyncQueueRefUnlocked AsyncQueue
queue = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueueRefUnlockedMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AsyncQueueRefUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueRefUnlocked

#endif

-- method AsyncQueue::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to remove from the @queue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_remove" g_async_queue_remove :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr () ->                               -- item : TBasicType TPtr
    IO CInt

-- | Remove an item from the queue.
-- 
-- /Since: 2.46/
asyncQueueRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Ptr ()
    -- ^ /@item@/: the data to remove from the /@queue@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the item was removed
asyncQueueRemove :: AsyncQueue -> Ptr () -> m Bool
asyncQueueRemove AsyncQueue
queue Ptr ()
item = IO Bool -> m Bool
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 (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AsyncQueueRemoveMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.MethodInfo AsyncQueueRemoveMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueRemove

#endif

-- method AsyncQueue::remove_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to remove from the @queue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_remove_unlocked" g_async_queue_remove_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr () ->                               -- item : TBasicType TPtr
    IO CInt

-- | Remove an item from the queue.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
-- 
-- /Since: 2.46/
asyncQueueRemoveUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Ptr ()
    -- ^ /@item@/: the data to remove from the /@queue@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the item was removed
asyncQueueRemoveUnlocked :: AsyncQueue -> Ptr () -> m Bool
asyncQueueRemoveUnlocked AsyncQueue
queue Ptr ()
item = IO Bool -> m Bool
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 (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AsyncQueueRemoveUnlockedMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.MethodInfo AsyncQueueRemoveUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueRemoveUnlocked

#endif

-- method AsyncQueue::timed_pop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_time"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "TimeVal" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTimeVal, determining the final time"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_timed_pop" g_async_queue_timed_pop :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr GLib.TimeVal.TimeVal ->             -- end_time : TInterface (Name {namespace = "GLib", name = "TimeVal"})
    IO (Ptr ())

{-# DEPRECATED asyncQueueTimedPop ["use 'GI.GLib.Structs.AsyncQueue.asyncQueueTimeoutPop'."] #-}
-- | Pops data from the /@queue@/. If the queue is empty, blocks until
-- /@endTime@/ or until data becomes available.
-- 
-- If no data is received before /@endTime@/, 'P.Nothing' is returned.
-- 
-- To easily calculate /@endTime@/, a combination of 'GI.GLib.Functions.getRealTime'
-- and 'GI.GLib.Structs.TimeVal.timeValAdd' can be used.
asyncQueueTimedPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> GLib.TimeVal.TimeVal
    -- ^ /@endTime@/: a t'GI.GLib.Structs.TimeVal.TimeVal', determining the final time
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue or 'P.Nothing', when no data is
    --     received before /@endTime@/.
asyncQueueTimedPop :: AsyncQueue -> TimeVal -> m (Ptr ())
asyncQueueTimedPop AsyncQueue
queue TimeVal
endTime = IO (Ptr ()) -> m (Ptr ())
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 (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.MethodInfo AsyncQueueTimedPopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimedPop

#endif

-- method AsyncQueue::timed_pop_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_time"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "TimeVal" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTimeVal, determining the final time"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_timed_pop_unlocked" g_async_queue_timed_pop_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Ptr GLib.TimeVal.TimeVal ->             -- end_time : TInterface (Name {namespace = "GLib", name = "TimeVal"})
    IO (Ptr ())

{-# DEPRECATED asyncQueueTimedPopUnlocked ["use 'GI.GLib.Structs.AsyncQueue.asyncQueueTimeoutPopUnlocked'."] #-}
-- | Pops data from the /@queue@/. If the queue is empty, blocks until
-- /@endTime@/ or until data becomes available.
-- 
-- If no data is received before /@endTime@/, 'P.Nothing' is returned.
-- 
-- To easily calculate /@endTime@/, a combination of 'GI.GLib.Functions.getRealTime'
-- and 'GI.GLib.Structs.TimeVal.timeValAdd' can be used.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
asyncQueueTimedPopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> GLib.TimeVal.TimeVal
    -- ^ /@endTime@/: a t'GI.GLib.Structs.TimeVal.TimeVal', determining the final time
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue or 'P.Nothing', when no data is
    --     received before /@endTime@/.
asyncQueueTimedPopUnlocked :: AsyncQueue -> TimeVal -> m (Ptr ())
asyncQueueTimedPopUnlocked AsyncQueue
queue TimeVal
endTime = IO (Ptr ()) -> m (Ptr ())
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 (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.MethodInfo AsyncQueueTimedPopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimedPopUnlocked

#endif

-- method AsyncQueue::timeout_pop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of microseconds to wait"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_timeout_pop" g_async_queue_timeout_pop :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Word64 ->                               -- timeout : TBasicType TUInt64
    IO (Ptr ())

-- | Pops data from the /@queue@/. If the queue is empty, blocks for
-- /@timeout@/ microseconds, or until data becomes available.
-- 
-- If no data is received before the timeout, 'P.Nothing' is returned.
asyncQueueTimeoutPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Word64
    -- ^ /@timeout@/: the number of microseconds to wait
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue or 'P.Nothing', when no data is
    --     received before the timeout.
asyncQueueTimeoutPop :: AsyncQueue -> Word64 -> m (Ptr ())
asyncQueueTimeoutPop AsyncQueue
queue Word64
timeout = IO (Ptr ()) -> m (Ptr ())
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 (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueueTimeoutPopMethodInfo
instance (signature ~ (Word64 -> m (Ptr ())), MonadIO m) => O.MethodInfo AsyncQueueTimeoutPopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimeoutPop

#endif

-- method AsyncQueue::timeout_pop_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of microseconds to wait"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_timeout_pop_unlocked" g_async_queue_timeout_pop_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    Word64 ->                               -- timeout : TBasicType TUInt64
    IO (Ptr ())

-- | Pops data from the /@queue@/. If the queue is empty, blocks for
-- /@timeout@/ microseconds, or until data becomes available.
-- 
-- If no data is received before the timeout, 'P.Nothing' is returned.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
asyncQueueTimeoutPopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> Word64
    -- ^ /@timeout@/: the number of microseconds to wait
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue or 'P.Nothing', when no data is
    --     received before the timeout.
asyncQueueTimeoutPopUnlocked :: AsyncQueue -> Word64 -> m (Ptr ())
asyncQueueTimeoutPopUnlocked AsyncQueue
queue Word64
timeout = IO (Ptr ()) -> m (Ptr ())
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 (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueueTimeoutPopUnlockedMethodInfo
instance (signature ~ (Word64 -> m (Ptr ())), MonadIO m) => O.MethodInfo AsyncQueueTimeoutPopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTimeoutPopUnlocked

#endif

-- method AsyncQueue::try_pop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_try_pop" g_async_queue_try_pop :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO (Ptr ())

-- | Tries to pop data from the /@queue@/. If no data is available,
-- 'P.Nothing' is returned.
asyncQueueTryPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue or 'P.Nothing', when no data is
    --     available immediately.
asyncQueueTryPop :: AsyncQueue -> m (Ptr ())
asyncQueueTryPop AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
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 (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueueTryPopMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo AsyncQueueTryPopMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTryPop

#endif

-- method AsyncQueue::try_pop_unlocked
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "AsyncQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_async_queue_try_pop_unlocked" g_async_queue_try_pop_unlocked :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO (Ptr ())

-- | Tries to pop data from the /@queue@/. If no data is available,
-- 'P.Nothing' is returned.
-- 
-- This function must be called while holding the /@queue@/\'s lock.
asyncQueueTryPopUnlocked ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m (Ptr ())
    -- ^ __Returns:__ data from the queue or 'P.Nothing', when no data is
    --     available immediately.
asyncQueueTryPopUnlocked :: AsyncQueue -> m (Ptr ())
asyncQueueTryPopUnlocked AsyncQueue
queue = IO (Ptr ()) -> m (Ptr ())
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 (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AsyncQueueTryPopUnlockedMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo AsyncQueueTryPopUnlockedMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueTryPopUnlocked

#endif

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

foreign import ccall "g_async_queue_unlock" g_async_queue_unlock :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO ()

-- | Releases the queue\'s lock.
-- 
-- Calling this function when you have not acquired
-- the with 'GI.GLib.Structs.AsyncQueue.asyncQueueLock' leads to undefined
-- behaviour.
asyncQueueUnlock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m ()
asyncQueueUnlock :: AsyncQueue -> m ()
asyncQueueUnlock AsyncQueue
queue = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueueUnlockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AsyncQueueUnlockMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueUnlock

#endif

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

foreign import ccall "g_async_queue_unref" g_async_queue_unref :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "AsyncQueue"})
    IO ()

-- | Decreases the reference count of the asynchronous /@queue@/ by 1.
-- 
-- If the reference count went to 0, the /@queue@/ will be destroyed
-- and the memory allocated will be freed. So you are not allowed
-- to use the /@queue@/ afterwards, as it might have disappeared.
-- You do not need to hold the lock to call this function.
asyncQueueUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'.
    -> m ()
asyncQueueUnref :: AsyncQueue -> m ()
asyncQueueUnref AsyncQueue
queue = 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 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 Ptr AsyncQueue
queue'
    AsyncQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AsyncQueue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueueUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AsyncQueueUnrefMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueUnref

#endif

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

foreign import ccall "g_async_queue_unref_and_unlock" g_async_queue_unref_and_unlock :: 
    Ptr AsyncQueue ->                       -- queue : TInterface (Name {namespace = "GLib", name = "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."] #-}
-- | Decreases the reference count of the asynchronous /@queue@/ by 1
-- and releases the lock. This function must be called while holding
-- the /@queue@/\'s lock. If the reference count went to 0, the /@queue@/
-- will be destroyed and the memory allocated will be freed.
asyncQueueUnrefAndUnlock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AsyncQueue
    -- ^ /@queue@/: a t'GI.GLib.Structs.AsyncQueue.AsyncQueue'
    -> m ()
asyncQueueUnrefAndUnlock :: AsyncQueue -> m ()
asyncQueueUnrefAndUnlock AsyncQueue
queue = 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 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AsyncQueueUnrefAndUnlockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AsyncQueueUnrefAndUnlockMethodInfo AsyncQueue signature where
    overloadedMethod = asyncQueueUnrefAndUnlock

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAsyncQueueMethod (t :: Symbol) (o :: *) :: * 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 "pushUnlocked" o = AsyncQueuePushUnlockedMethodInfo
    ResolveAsyncQueueMethod "refUnlocked" o = AsyncQueueRefUnlockedMethodInfo
    ResolveAsyncQueueMethod "remove" o = AsyncQueueRemoveMethodInfo
    ResolveAsyncQueueMethod "removeUnlocked" o = AsyncQueueRemoveUnlockedMethodInfo
    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 "unref" o = AsyncQueueUnrefMethodInfo
    ResolveAsyncQueueMethod "unrefAndUnlock" o = AsyncQueueUnrefAndUnlockMethodInfo
    ResolveAsyncQueueMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveAsyncQueueMethod t AsyncQueue, O.MethodInfo 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

#endif