{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Contains the public fields of a
-- [Queue][glib-Double-ended-Queues].

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

module GI.GLib.Structs.Queue
    ( 

-- * Exported types
    Queue(..)                               ,
    newZeroQueue                            ,
    noQueue                                 ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveQueueMethod                      ,
#endif


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    QueueClearMethodInfo                    ,
#endif
    queueClear                              ,


-- ** clearFull #method:clearFull#

#if defined(ENABLE_OVERLOADING)
    QueueClearFullMethodInfo                ,
#endif
    queueClearFull                          ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    QueueFreeMethodInfo                     ,
#endif
    queueFree                               ,


-- ** freeFull #method:freeFull#

#if defined(ENABLE_OVERLOADING)
    QueueFreeFullMethodInfo                 ,
#endif
    queueFreeFull                           ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    QueueGetLengthMethodInfo                ,
#endif
    queueGetLength                          ,


-- ** index #method:index#

#if defined(ENABLE_OVERLOADING)
    QueueIndexMethodInfo                    ,
#endif
    queueIndex                              ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    QueueInitMethodInfo                     ,
#endif
    queueInit                               ,


-- ** isEmpty #method:isEmpty#

#if defined(ENABLE_OVERLOADING)
    QueueIsEmptyMethodInfo                  ,
#endif
    queueIsEmpty                            ,


-- ** peekHead #method:peekHead#

#if defined(ENABLE_OVERLOADING)
    QueuePeekHeadMethodInfo                 ,
#endif
    queuePeekHead                           ,


-- ** peekNth #method:peekNth#

#if defined(ENABLE_OVERLOADING)
    QueuePeekNthMethodInfo                  ,
#endif
    queuePeekNth                            ,


-- ** peekTail #method:peekTail#

#if defined(ENABLE_OVERLOADING)
    QueuePeekTailMethodInfo                 ,
#endif
    queuePeekTail                           ,


-- ** popHead #method:popHead#

#if defined(ENABLE_OVERLOADING)
    QueuePopHeadMethodInfo                  ,
#endif
    queuePopHead                            ,


-- ** popNth #method:popNth#

#if defined(ENABLE_OVERLOADING)
    QueuePopNthMethodInfo                   ,
#endif
    queuePopNth                             ,


-- ** popTail #method:popTail#

#if defined(ENABLE_OVERLOADING)
    QueuePopTailMethodInfo                  ,
#endif
    queuePopTail                            ,


-- ** pushHead #method:pushHead#

#if defined(ENABLE_OVERLOADING)
    QueuePushHeadMethodInfo                 ,
#endif
    queuePushHead                           ,


-- ** pushNth #method:pushNth#

#if defined(ENABLE_OVERLOADING)
    QueuePushNthMethodInfo                  ,
#endif
    queuePushNth                            ,


-- ** pushTail #method:pushTail#

#if defined(ENABLE_OVERLOADING)
    QueuePushTailMethodInfo                 ,
#endif
    queuePushTail                           ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    QueueRemoveMethodInfo                   ,
#endif
    queueRemove                             ,


-- ** removeAll #method:removeAll#

#if defined(ENABLE_OVERLOADING)
    QueueRemoveAllMethodInfo                ,
#endif
    queueRemoveAll                          ,


-- ** reverse #method:reverse#

#if defined(ENABLE_OVERLOADING)
    QueueReverseMethodInfo                  ,
#endif
    queueReverse                            ,




 -- * Properties
-- ** head #attr:head#
-- | a pointer to the first element of the queue

    clearQueueHead                          ,
    getQueueHead                            ,
#if defined(ENABLE_OVERLOADING)
    queue_head                              ,
#endif
    setQueueHead                            ,


-- ** length #attr:length#
-- | the number of elements in the queue

    getQueueLength                          ,
#if defined(ENABLE_OVERLOADING)
    queue_length                            ,
#endif
    setQueueLength                          ,


-- ** tail #attr:tail#
-- | a pointer to the last element of the queue

    clearQueueTail                          ,
    getQueueTail                            ,
#if defined(ENABLE_OVERLOADING)
    queue_tail                              ,
#endif
    setQueueTail                            ,




    ) 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.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 Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GLib.Callbacks as GLib.Callbacks

-- | Memory-managed wrapper type.
newtype Queue = Queue (ManagedPtr Queue)
    deriving (Queue -> Queue -> Bool
(Queue -> Queue -> Bool) -> (Queue -> Queue -> Bool) -> Eq Queue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Queue -> Queue -> Bool
$c/= :: Queue -> Queue -> Bool
== :: Queue -> Queue -> Bool
$c== :: Queue -> Queue -> Bool
Eq)
instance WrappedPtr Queue where
    wrappedPtrCalloc :: IO (Ptr Queue)
wrappedPtrCalloc = Int -> IO (Ptr Queue)
forall a. Int -> IO (Ptr a)
callocBytes 24
    wrappedPtrCopy :: Queue -> IO Queue
wrappedPtrCopy = \p :: Queue
p -> Queue -> (Ptr Queue -> IO Queue) -> IO Queue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Queue
p (Int -> Ptr Queue -> IO (Ptr Queue)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 24 (Ptr Queue -> IO (Ptr Queue))
-> (Ptr Queue -> IO Queue) -> Ptr Queue -> IO Queue
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr Queue -> Queue) -> Ptr Queue -> IO Queue
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Queue -> Queue
Queue)
    wrappedPtrFree :: Maybe (GDestroyNotify Queue)
wrappedPtrFree = GDestroyNotify Queue -> Maybe (GDestroyNotify Queue)
forall a. a -> Maybe a
Just GDestroyNotify Queue
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `Queue` struct initialized to zero.
newZeroQueue :: MonadIO m => m Queue
newZeroQueue :: m Queue
newZeroQueue = IO Queue -> m Queue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Queue -> m Queue) -> IO Queue -> m Queue
forall a b. (a -> b) -> a -> b
$ IO (Ptr Queue)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr Queue) -> (Ptr Queue -> IO Queue) -> IO Queue
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Queue -> Queue) -> Ptr Queue -> IO Queue
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Queue -> Queue
Queue

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


-- | A convenience alias for `Nothing` :: `Maybe` `Queue`.
noQueue :: Maybe Queue
noQueue :: Maybe Queue
noQueue = Maybe Queue
forall a. Maybe a
Nothing

-- | Get the value of the “@head@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' queue #head
-- @
getQueueHead :: MonadIO m => Queue -> m ([Ptr ()])
getQueueHead :: Queue -> m [Ptr ()]
getQueueHead s :: Queue
s = 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
$ Queue -> (Ptr Queue -> IO [Ptr ()]) -> IO [Ptr ()]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Queue
s ((Ptr Queue -> IO [Ptr ()]) -> IO [Ptr ()])
-> (Ptr Queue -> IO [Ptr ()]) -> IO [Ptr ()]
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Queue
ptr -> do
    Ptr (GList (Ptr ()))
val <- Ptr (Ptr (GList (Ptr ()))) -> IO (Ptr (GList (Ptr ())))
forall a. Storable a => Ptr a -> IO a
peek (Ptr Queue
ptr Ptr Queue -> Int -> Ptr (Ptr (GList (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (Ptr (GList (Ptr ())))
    [Ptr ()]
val' <- Ptr (GList (Ptr ())) -> IO [Ptr ()]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ()))
val
    [Ptr ()] -> IO [Ptr ()]
forall (m :: * -> *) a. Monad m => a -> m a
return [Ptr ()]
val'

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

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

#if defined(ENABLE_OVERLOADING)
data QueueHeadFieldInfo
instance AttrInfo QueueHeadFieldInfo where
    type AttrBaseTypeConstraint QueueHeadFieldInfo = (~) Queue
    type AttrAllowedOps QueueHeadFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint QueueHeadFieldInfo = (~) (Ptr (GList (Ptr ())))
    type AttrTransferTypeConstraint QueueHeadFieldInfo = (~)(Ptr (GList (Ptr ())))
    type AttrTransferType QueueHeadFieldInfo = (Ptr (GList (Ptr ())))
    type AttrGetType QueueHeadFieldInfo = [Ptr ()]
    type AttrLabel QueueHeadFieldInfo = "head"
    type AttrOrigin QueueHeadFieldInfo = Queue
    attrGet = getQueueHead
    attrSet = setQueueHead
    attrConstruct = undefined
    attrClear = clearQueueHead
    attrTransfer _ v = do
        return v

queue_head :: AttrLabelProxy "head"
queue_head = AttrLabelProxy

#endif


-- | Get the value of the “@tail@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' queue #tail
-- @
getQueueTail :: MonadIO m => Queue -> m ([Ptr ()])
getQueueTail :: Queue -> m [Ptr ()]
getQueueTail s :: Queue
s = 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
$ Queue -> (Ptr Queue -> IO [Ptr ()]) -> IO [Ptr ()]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Queue
s ((Ptr Queue -> IO [Ptr ()]) -> IO [Ptr ()])
-> (Ptr Queue -> IO [Ptr ()]) -> IO [Ptr ()]
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Queue
ptr -> do
    Ptr (GList (Ptr ()))
val <- Ptr (Ptr (GList (Ptr ()))) -> IO (Ptr (GList (Ptr ())))
forall a. Storable a => Ptr a -> IO a
peek (Ptr Queue
ptr Ptr Queue -> Int -> Ptr (Ptr (GList (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO (Ptr (GList (Ptr ())))
    [Ptr ()]
val' <- Ptr (GList (Ptr ())) -> IO [Ptr ()]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ()))
val
    [Ptr ()] -> IO [Ptr ()]
forall (m :: * -> *) a. Monad m => a -> m a
return [Ptr ()]
val'

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

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

#if defined(ENABLE_OVERLOADING)
data QueueTailFieldInfo
instance AttrInfo QueueTailFieldInfo where
    type AttrBaseTypeConstraint QueueTailFieldInfo = (~) Queue
    type AttrAllowedOps QueueTailFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint QueueTailFieldInfo = (~) (Ptr (GList (Ptr ())))
    type AttrTransferTypeConstraint QueueTailFieldInfo = (~)(Ptr (GList (Ptr ())))
    type AttrTransferType QueueTailFieldInfo = (Ptr (GList (Ptr ())))
    type AttrGetType QueueTailFieldInfo = [Ptr ()]
    type AttrLabel QueueTailFieldInfo = "tail"
    type AttrOrigin QueueTailFieldInfo = Queue
    attrGet = getQueueTail
    attrSet = setQueueTail
    attrConstruct = undefined
    attrClear = clearQueueTail
    attrTransfer _ v = do
        return v

queue_tail :: AttrLabelProxy "tail"
queue_tail = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data QueueLengthFieldInfo
instance AttrInfo QueueLengthFieldInfo where
    type AttrBaseTypeConstraint QueueLengthFieldInfo = (~) Queue
    type AttrAllowedOps QueueLengthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint QueueLengthFieldInfo = (~) Word32
    type AttrTransferTypeConstraint QueueLengthFieldInfo = (~)Word32
    type AttrTransferType QueueLengthFieldInfo = Word32
    type AttrGetType QueueLengthFieldInfo = Word32
    type AttrLabel QueueLengthFieldInfo = "length"
    type AttrOrigin QueueLengthFieldInfo = Queue
    attrGet = getQueueLength
    attrSet = setQueueLength
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

queue_length :: AttrLabelProxy "length"
queue_length = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Queue
type instance O.AttributeList Queue = QueueAttributeList
type QueueAttributeList = ('[ '("head", QueueHeadFieldInfo), '("tail", QueueTailFieldInfo), '("length", QueueLengthFieldInfo)] :: [(Symbol, *)])
#endif

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

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

-- | Removes all the elements in /@queue@/. If queue elements contain
-- dynamically-allocated memory, they should be freed first.
-- 
-- /Since: 2.14/
queueClear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m ()
queueClear :: Queue -> m ()
queueClear queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr Queue -> IO ()
g_queue_clear Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueueClearMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo QueueClearMethodInfo Queue signature where
    overloadedMethod = queueClear

#endif

-- method Queue::clear_full
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GQueue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the function to be called to free memory allocated"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_queue_clear_full" g_queue_clear_full :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Convenience method, which frees all the memory used by a t'GI.GLib.Structs.Queue.Queue',
-- and calls the provided /@freeFunc@/ on each item in the t'GI.GLib.Structs.Queue.Queue'.
-- 
-- /Since: 2.60/
queueClearFull ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a pointer to a t'GI.GLib.Structs.Queue.Queue'
    -> Maybe (GLib.Callbacks.DestroyNotify)
    -- ^ /@freeFunc@/: the function to be called to free memory allocated
    -> m ()
queueClearFull :: Queue -> Maybe DestroyNotify -> m ()
queueClearFull queue :: Queue
queue freeFunc :: Maybe DestroyNotify
freeFunc = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    FunPtr DestroyNotify
maybeFreeFunc <- case Maybe DestroyNotify
freeFunc of
        Nothing -> FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr DestroyNotify
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just jFreeFunc :: DestroyNotify
jFreeFunc -> do
            Ptr (FunPtr DestroyNotify)
ptrfreeFunc <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
            FunPtr DestroyNotify
jFreeFunc' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptrfreeFunc) DestroyNotify
jFreeFunc)
            Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptrfreeFunc FunPtr DestroyNotify
jFreeFunc'
            FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr DestroyNotify
jFreeFunc'
    Ptr Queue -> FunPtr DestroyNotify -> IO ()
g_queue_clear_full Ptr Queue
queue' FunPtr DestroyNotify
maybeFreeFunc
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueueClearFullMethodInfo
instance (signature ~ (Maybe (GLib.Callbacks.DestroyNotify) -> m ()), MonadIO m) => O.MethodInfo QueueClearFullMethodInfo Queue signature where
    overloadedMethod = queueClearFull

#endif

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

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

-- | Frees the memory allocated for the t'GI.GLib.Structs.Queue.Queue'. Only call this function
-- if /@queue@/ was created with @/g_queue_new()/@. If queue elements contain
-- dynamically-allocated memory, they should be freed first.
-- 
-- If queue elements contain dynamically-allocated memory, you should
-- either use 'GI.GLib.Structs.Queue.queueFreeFull' or free them manually first.
queueFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m ()
queueFree :: Queue -> m ()
queueFree queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr Queue -> IO ()
g_queue_free Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueueFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo QueueFreeMethodInfo Queue signature where
    overloadedMethod = queueFree

#endif

-- method Queue::free_full
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GQueue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the function to be called to free each element's data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_queue_free_full" g_queue_free_full :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Convenience method, which frees all the memory used by a t'GI.GLib.Structs.Queue.Queue',
-- and calls the specified destroy function on every element\'s data.
-- 
-- /@freeFunc@/ should not modify the queue (eg, by removing the freed
-- element from it).
-- 
-- /Since: 2.32/
queueFreeFull ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a pointer to a t'GI.GLib.Structs.Queue.Queue'
    -> GLib.Callbacks.DestroyNotify
    -- ^ /@freeFunc@/: the function to be called to free each element\'s data
    -> m ()
queueFreeFull :: Queue -> DestroyNotify -> m ()
queueFreeFull queue :: Queue
queue freeFunc :: DestroyNotify
freeFunc = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr (FunPtr DestroyNotify)
ptrfreeFunc <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
    FunPtr DestroyNotify
freeFunc' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptrfreeFunc) DestroyNotify
freeFunc)
    Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptrfreeFunc FunPtr DestroyNotify
freeFunc'
    Ptr Queue -> FunPtr DestroyNotify -> IO ()
g_queue_free_full Ptr Queue
queue' FunPtr DestroyNotify
freeFunc'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueueFreeFullMethodInfo
instance (signature ~ (GLib.Callbacks.DestroyNotify -> m ()), MonadIO m) => O.MethodInfo QueueFreeFullMethodInfo Queue signature where
    overloadedMethod = queueFreeFull

#endif

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

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

-- | Returns the number of items in /@queue@/.
-- 
-- /Since: 2.4/
queueGetLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m Word32
    -- ^ __Returns:__ the number of items in /@queue@/
queueGetLength :: Queue -> m Word32
queueGetLength queue :: Queue
queue = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Word32
result <- Ptr Queue -> IO Word32
g_queue_get_length Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data QueueGetLengthMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo QueueGetLengthMethodInfo Queue signature where
    overloadedMethod = queueGetLength

#endif

-- method Queue::index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue" , 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 "the data to find" , 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_queue_index" g_queue_index :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO Int32

-- | Returns the position of the first element in /@queue@/ which contains /@data@/.
-- 
-- /Since: 2.4/
queueIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> Ptr ()
    -- ^ /@data@/: the data to find
    -> m Int32
    -- ^ __Returns:__ the position of the first element in /@queue@/ which
    --     contains /@data@/, or -1 if no element in /@queue@/ contains /@data@/
queueIndex :: Queue -> Ptr () -> m Int32
queueIndex queue :: Queue
queue data_ :: Ptr ()
data_ = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Int32
result <- Ptr Queue -> Ptr () -> IO Int32
g_queue_index Ptr Queue
queue' Ptr ()
data_
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data QueueIndexMethodInfo
instance (signature ~ (Ptr () -> m Int32), MonadIO m) => O.MethodInfo QueueIndexMethodInfo Queue signature where
    overloadedMethod = queueIndex

#endif

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

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

-- | A statically-allocated t'GI.GLib.Structs.Queue.Queue' must be initialized with this function
-- before it can be used. Alternatively you can initialize it with
-- @/G_QUEUE_INIT/@. It is not necessary to initialize queues created with
-- @/g_queue_new()/@.
-- 
-- /Since: 2.14/
queueInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: an uninitialized t'GI.GLib.Structs.Queue.Queue'
    -> m ()
queueInit :: Queue -> m ()
queueInit queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr Queue -> IO ()
g_queue_init Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueueInitMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo QueueInitMethodInfo Queue signature where
    overloadedMethod = queueInit

#endif

-- method Queue::is_empty
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue." , 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_queue_is_empty" g_queue_is_empty :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    IO CInt

-- | Returns 'P.True' if the queue is empty.
queueIsEmpty ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the queue is empty
queueIsEmpty :: Queue -> m Bool
queueIsEmpty queue :: Queue
queue = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    CInt
result <- Ptr Queue -> IO CInt
g_queue_is_empty Ptr Queue
queue'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data QueueIsEmptyMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo QueueIsEmptyMethodInfo Queue signature where
    overloadedMethod = queueIsEmpty

#endif

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

-- | Returns the first element of the queue.
queuePeekHead ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m (Ptr ())
    -- ^ __Returns:__ the data of the first element in the queue, or 'P.Nothing'
    --     if the queue is empty
queuePeekHead :: Queue -> m (Ptr ())
queuePeekHead queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr ()
result <- Ptr Queue -> IO (Ptr ())
g_queue_peek_head Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data QueuePeekHeadMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo QueuePeekHeadMethodInfo Queue signature where
    overloadedMethod = queuePeekHead

#endif

-- method Queue::peek_nth
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position of the element"
--                 , 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_queue_peek_nth" g_queue_peek_nth :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    Word32 ->                               -- n : TBasicType TUInt
    IO (Ptr ())

-- | Returns the /@n@/\'th element of /@queue@/.
-- 
-- /Since: 2.4/
queuePeekNth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> Word32
    -- ^ /@n@/: the position of the element
    -> m (Ptr ())
    -- ^ __Returns:__ the data for the /@n@/\'th element of /@queue@/,
    --     or 'P.Nothing' if /@n@/ is off the end of /@queue@/
queuePeekNth :: Queue -> Word32 -> m (Ptr ())
queuePeekNth queue :: Queue
queue n :: Word32
n = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr ()
result <- Ptr Queue -> Word32 -> IO (Ptr ())
g_queue_peek_nth Ptr Queue
queue' Word32
n
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data QueuePeekNthMethodInfo
instance (signature ~ (Word32 -> m (Ptr ())), MonadIO m) => O.MethodInfo QueuePeekNthMethodInfo Queue signature where
    overloadedMethod = queuePeekNth

#endif

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

-- | Returns the last element of the queue.
queuePeekTail ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m (Ptr ())
    -- ^ __Returns:__ the data of the last element in the queue, or 'P.Nothing'
    --     if the queue is empty
queuePeekTail :: Queue -> m (Ptr ())
queuePeekTail queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr ()
result <- Ptr Queue -> IO (Ptr ())
g_queue_peek_tail Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data QueuePeekTailMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo QueuePeekTailMethodInfo Queue signature where
    overloadedMethod = queuePeekTail

#endif

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

-- | Removes the first element of the queue and returns its data.
queuePopHead ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m (Ptr ())
    -- ^ __Returns:__ the data of the first element in the queue, or 'P.Nothing'
    --     if the queue is empty
queuePopHead :: Queue -> m (Ptr ())
queuePopHead queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr ()
result <- Ptr Queue -> IO (Ptr ())
g_queue_pop_head Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data QueuePopHeadMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo QueuePopHeadMethodInfo Queue signature where
    overloadedMethod = queuePopHead

#endif

-- method Queue::pop_nth
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position of the element"
--                 , 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_queue_pop_nth" g_queue_pop_nth :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    Word32 ->                               -- n : TBasicType TUInt
    IO (Ptr ())

-- | Removes the /@n@/\'th element of /@queue@/ and returns its data.
-- 
-- /Since: 2.4/
queuePopNth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> Word32
    -- ^ /@n@/: the position of the element
    -> m (Ptr ())
    -- ^ __Returns:__ the element\'s data, or 'P.Nothing' if /@n@/ is off the end of /@queue@/
queuePopNth :: Queue -> Word32 -> m (Ptr ())
queuePopNth queue :: Queue
queue n :: Word32
n = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr ()
result <- Ptr Queue -> Word32 -> IO (Ptr ())
g_queue_pop_nth Ptr Queue
queue' Word32
n
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data QueuePopNthMethodInfo
instance (signature ~ (Word32 -> m (Ptr ())), MonadIO m) => O.MethodInfo QueuePopNthMethodInfo Queue signature where
    overloadedMethod = queuePopNth

#endif

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

-- | Removes the last element of the queue and returns its data.
queuePopTail ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m (Ptr ())
    -- ^ __Returns:__ the data of the last element in the queue, or 'P.Nothing'
    --     if the queue is empty
queuePopTail :: Queue -> m (Ptr ())
queuePopTail queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr ()
result <- Ptr Queue -> IO (Ptr ())
g_queue_pop_tail Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data QueuePopTailMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo QueuePopTailMethodInfo Queue signature where
    overloadedMethod = queuePopTail

#endif

-- method Queue::push_head
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue." , 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 "the data for the new element."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Adds a new element at the head of the queue.
queuePushHead ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'.
    -> Ptr ()
    -- ^ /@data@/: the data for the new element.
    -> m ()
queuePushHead :: Queue -> Ptr () -> m ()
queuePushHead queue :: Queue
queue data_ :: 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr Queue -> DestroyNotify
g_queue_push_head Ptr Queue
queue' Ptr ()
data_
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueuePushHeadMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo QueuePushHeadMethodInfo Queue signature where
    overloadedMethod = queuePushHead

#endif

-- method Queue::push_nth
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue" , 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 "the data for the new element"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the position to insert the new element. If @n is negative or\n    larger than the number of elements in the @queue, the element is\n    added to the end of 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_queue_push_nth" g_queue_push_nth :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    Ptr () ->                               -- data : TBasicType TPtr
    Int32 ->                                -- n : TBasicType TInt
    IO ()

-- | Inserts a new element into /@queue@/ at the given position.
-- 
-- /Since: 2.4/
queuePushNth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> Ptr ()
    -- ^ /@data@/: the data for the new element
    -> Int32
    -- ^ /@n@/: the position to insert the new element. If /@n@/ is negative or
    --     larger than the number of elements in the /@queue@/, the element is
    --     added to the end of the queue.
    -> m ()
queuePushNth :: Queue -> Ptr () -> Int32 -> m ()
queuePushNth queue :: Queue
queue data_ :: Ptr ()
data_ n :: Int32
n = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr Queue -> Ptr () -> Int32 -> IO ()
g_queue_push_nth Ptr Queue
queue' Ptr ()
data_ Int32
n
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueuePushNthMethodInfo
instance (signature ~ (Ptr () -> Int32 -> m ()), MonadIO m) => O.MethodInfo QueuePushNthMethodInfo Queue signature where
    overloadedMethod = queuePushNth

#endif

-- method Queue::push_tail
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue" , 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 "the data for the new element"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Adds a new element at the tail of the queue.
queuePushTail ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> Ptr ()
    -- ^ /@data@/: the data for the new element
    -> m ()
queuePushTail :: Queue -> Ptr () -> m ()
queuePushTail queue :: Queue
queue data_ :: 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr Queue -> DestroyNotify
g_queue_push_tail Ptr Queue
queue' Ptr ()
data_
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueuePushTailMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo QueuePushTailMethodInfo Queue signature where
    overloadedMethod = queuePushTail

#endif

-- method Queue::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue" , 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 "the data to remove" , 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_queue_remove" g_queue_remove :: 
    Ptr Queue ->                            -- queue : TInterface (Name {namespace = "GLib", name = "Queue"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO CInt

-- | Removes the first element in /@queue@/ that contains /@data@/.
-- 
-- /Since: 2.4/
queueRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> Ptr ()
    -- ^ /@data@/: the data to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@data@/ was found and removed from /@queue@/
queueRemove :: Queue -> Ptr () -> m Bool
queueRemove queue :: Queue
queue data_ :: Ptr ()
data_ = 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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    CInt
result <- Ptr Queue -> Ptr () -> IO CInt
g_queue_remove Ptr Queue
queue' Ptr ()
data_
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data QueueRemoveMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.MethodInfo QueueRemoveMethodInfo Queue signature where
    overloadedMethod = queueRemove

#endif

-- method Queue::remove_all
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType = TInterface Name { namespace = "GLib" , name = "Queue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GQueue" , 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 "the data to remove" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

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

-- | Remove all elements whose data equals /@data@/ from /@queue@/.
-- 
-- /Since: 2.4/
queueRemoveAll ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> Ptr ()
    -- ^ /@data@/: the data to remove
    -> m Word32
    -- ^ __Returns:__ the number of elements removed from /@queue@/
queueRemoveAll :: Queue -> Ptr () -> m Word32
queueRemoveAll queue :: Queue
queue data_ :: Ptr ()
data_ = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Word32
result <- Ptr Queue -> Ptr () -> IO Word32
g_queue_remove_all Ptr Queue
queue' Ptr ()
data_
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data QueueRemoveAllMethodInfo
instance (signature ~ (Ptr () -> m Word32), MonadIO m) => O.MethodInfo QueueRemoveAllMethodInfo Queue signature where
    overloadedMethod = queueRemoveAll

#endif

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

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

-- | Reverses the order of the items in /@queue@/.
-- 
-- /Since: 2.4/
queueReverse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Queue
    -- ^ /@queue@/: a t'GI.GLib.Structs.Queue.Queue'
    -> m ()
queueReverse :: Queue -> m ()
queueReverse queue :: Queue
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 Queue
queue' <- Queue -> IO (Ptr Queue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Queue
queue
    Ptr Queue -> IO ()
g_queue_reverse Ptr Queue
queue'
    Queue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Queue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QueueReverseMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo QueueReverseMethodInfo Queue signature where
    overloadedMethod = queueReverse

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveQueueMethod (t :: Symbol) (o :: *) :: * where
    ResolveQueueMethod "clear" o = QueueClearMethodInfo
    ResolveQueueMethod "clearFull" o = QueueClearFullMethodInfo
    ResolveQueueMethod "free" o = QueueFreeMethodInfo
    ResolveQueueMethod "freeFull" o = QueueFreeFullMethodInfo
    ResolveQueueMethod "index" o = QueueIndexMethodInfo
    ResolveQueueMethod "init" o = QueueInitMethodInfo
    ResolveQueueMethod "isEmpty" o = QueueIsEmptyMethodInfo
    ResolveQueueMethod "peekHead" o = QueuePeekHeadMethodInfo
    ResolveQueueMethod "peekNth" o = QueuePeekNthMethodInfo
    ResolveQueueMethod "peekTail" o = QueuePeekTailMethodInfo
    ResolveQueueMethod "popHead" o = QueuePopHeadMethodInfo
    ResolveQueueMethod "popNth" o = QueuePopNthMethodInfo
    ResolveQueueMethod "popTail" o = QueuePopTailMethodInfo
    ResolveQueueMethod "pushHead" o = QueuePushHeadMethodInfo
    ResolveQueueMethod "pushNth" o = QueuePushNthMethodInfo
    ResolveQueueMethod "pushTail" o = QueuePushTailMethodInfo
    ResolveQueueMethod "remove" o = QueueRemoveMethodInfo
    ResolveQueueMethod "removeAll" o = QueueRemoveAllMethodInfo
    ResolveQueueMethod "reverse" o = QueueReverseMethodInfo
    ResolveQueueMethod "getLength" o = QueueGetLengthMethodInfo
    ResolveQueueMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveQueueMethod t Queue, O.MethodInfo info Queue p) => OL.IsLabel t (Queue -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif