{-# 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)
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)
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)
AsyncQueueUnrefMethodInfo ,
#endif
asyncQueueUnref ,
#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
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
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
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 :: 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
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 :: 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
foreign import ccall "g_async_queue_lock" g_async_queue_lock ::
Ptr AsyncQueue ->
IO ()
asyncQueueLock ::
(B.CallStack.HasCallStack, MonadIO m) =>
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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
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 :: 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
foreign import ccall "g_async_queue_unlock" g_async_queue_unlock ::
Ptr AsyncQueue ->
IO ()
asyncQueueUnlock ::
(B.CallStack.HasCallStack, MonadIO m) =>
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
foreign import ccall "g_async_queue_unref" g_async_queue_unref ::
Ptr AsyncQueue ->
IO ()
asyncQueueUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
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
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 :: 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