{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gst.Structs.AtomicQueue.AtomicQueue' object implements a queue that can be used from multiple
-- threads without performing any blocking operations.

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

module GI.Gst.Structs.AtomicQueue
    ( 

-- * Exported types
    AtomicQueue(..)                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAtomicQueueMethod                ,
#endif


-- ** length #method:length#

#if defined(ENABLE_OVERLOADING)
    AtomicQueueLengthMethodInfo             ,
#endif
    atomicQueueLength                       ,


-- ** new #method:new#

    atomicQueueNew                          ,


-- ** peek #method:peek#

#if defined(ENABLE_OVERLOADING)
    AtomicQueuePeekMethodInfo               ,
#endif
    atomicQueuePeek                         ,


-- ** pop #method:pop#

#if defined(ENABLE_OVERLOADING)
    AtomicQueuePopMethodInfo                ,
#endif
    atomicQueuePop                          ,


-- ** push #method:push#

#if defined(ENABLE_OVERLOADING)
    AtomicQueuePushMethodInfo               ,
#endif
    atomicQueuePush                         ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    AtomicQueueRefMethodInfo                ,
#endif
    atomicQueueRef                          ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    AtomicQueueUnrefMethodInfo              ,
#endif
    atomicQueueUnref                        ,




    ) 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


-- | Memory-managed wrapper type.
newtype AtomicQueue = AtomicQueue (SP.ManagedPtr AtomicQueue)
    deriving (AtomicQueue -> AtomicQueue -> Bool
(AtomicQueue -> AtomicQueue -> Bool)
-> (AtomicQueue -> AtomicQueue -> Bool) -> Eq AtomicQueue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AtomicQueue -> AtomicQueue -> Bool
$c/= :: AtomicQueue -> AtomicQueue -> Bool
== :: AtomicQueue -> AtomicQueue -> Bool
$c== :: AtomicQueue -> AtomicQueue -> Bool
Eq)

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

foreign import ccall "gst_atomic_queue_get_type" c_gst_atomic_queue_get_type :: 
    IO GType

type instance O.ParentTypes AtomicQueue = '[]
instance O.HasParentTypes AtomicQueue

instance B.Types.TypedObject AtomicQueue where
    glibType :: IO GType
glibType = IO GType
c_gst_atomic_queue_get_type

instance B.Types.GBoxed AtomicQueue

-- | Convert 'AtomicQueue' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue AtomicQueue where
    toGValue :: AtomicQueue -> IO GValue
toGValue AtomicQueue
o = do
        GType
gtype <- IO GType
c_gst_atomic_queue_get_type
        AtomicQueue -> (Ptr AtomicQueue -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AtomicQueue
o (GType
-> (GValue -> Ptr AtomicQueue -> IO ())
-> Ptr AtomicQueue
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr AtomicQueue -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO AtomicQueue
fromGValue GValue
gv = do
        Ptr AtomicQueue
ptr <- GValue -> IO (Ptr AtomicQueue)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr AtomicQueue)
        (ManagedPtr AtomicQueue -> AtomicQueue)
-> Ptr AtomicQueue -> IO AtomicQueue
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr AtomicQueue -> AtomicQueue
AtomicQueue Ptr AtomicQueue
ptr
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AtomicQueue
type instance O.AttributeList AtomicQueue = AtomicQueueAttributeList
type AtomicQueueAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method AtomicQueue::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "initial_size"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "initial queue size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "AtomicQueue" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_atomic_queue_new" gst_atomic_queue_new :: 
    Word32 ->                               -- initial_size : TBasicType TUInt
    IO (Ptr AtomicQueue)

-- | Create a new atomic queue instance. /@initialSize@/ will be rounded up to the
-- nearest power of 2 and used as the initial size of the queue.
atomicQueueNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word32
    -- ^ /@initialSize@/: initial queue size
    -> m AtomicQueue
    -- ^ __Returns:__ a new t'GI.Gst.Structs.AtomicQueue.AtomicQueue'
atomicQueueNew :: Word32 -> m AtomicQueue
atomicQueueNew Word32
initialSize = IO AtomicQueue -> m AtomicQueue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AtomicQueue -> m AtomicQueue)
-> IO AtomicQueue -> m AtomicQueue
forall a b. (a -> b) -> a -> b
$ do
    Ptr AtomicQueue
result <- Word32 -> IO (Ptr AtomicQueue)
gst_atomic_queue_new Word32
initialSize
    Text -> Ptr AtomicQueue -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"atomicQueueNew" Ptr AtomicQueue
result
    AtomicQueue
result' <- ((ManagedPtr AtomicQueue -> AtomicQueue)
-> Ptr AtomicQueue -> IO AtomicQueue
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AtomicQueue -> AtomicQueue
AtomicQueue) Ptr AtomicQueue
result
    AtomicQueue -> IO AtomicQueue
forall (m :: * -> *) a. Monad m => a -> m a
return AtomicQueue
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method AtomicQueue::length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "AtomicQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAtomicQueue" , 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 "gst_atomic_queue_length" gst_atomic_queue_length :: 
    Ptr AtomicQueue ->                      -- queue : TInterface (Name {namespace = "Gst", name = "AtomicQueue"})
    IO Word32

-- | Get the amount of items in the queue.
atomicQueueLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AtomicQueue
    -- ^ /@queue@/: a t'GI.Gst.Structs.AtomicQueue.AtomicQueue'
    -> m Word32
    -- ^ __Returns:__ the number of elements in the queue.
atomicQueueLength :: AtomicQueue -> m Word32
atomicQueueLength AtomicQueue
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 AtomicQueue
queue' <- AtomicQueue -> IO (Ptr AtomicQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AtomicQueue
queue
    Word32
result <- Ptr AtomicQueue -> IO Word32
gst_atomic_queue_length Ptr AtomicQueue
queue'
    AtomicQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AtomicQueue
queue
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data AtomicQueueLengthMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo AtomicQueueLengthMethodInfo AtomicQueue signature where
    overloadedMethod = atomicQueueLength

#endif

-- method AtomicQueue::peek
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "AtomicQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAtomicQueue" , 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 "gst_atomic_queue_peek" gst_atomic_queue_peek :: 
    Ptr AtomicQueue ->                      -- queue : TInterface (Name {namespace = "Gst", name = "AtomicQueue"})
    IO (Ptr ())

-- | Peek the head element of the queue without removing it from the queue.
atomicQueuePeek ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AtomicQueue
    -- ^ /@queue@/: a t'GI.Gst.Structs.AtomicQueue.AtomicQueue'
    -> m (Ptr ())
    -- ^ __Returns:__ the head element of /@queue@/ or
    -- 'P.Nothing' when the queue is empty.
atomicQueuePeek :: AtomicQueue -> m (Ptr ())
atomicQueuePeek AtomicQueue
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 AtomicQueue
queue' <- AtomicQueue -> IO (Ptr AtomicQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AtomicQueue
queue
    Ptr ()
result <- Ptr AtomicQueue -> IO (Ptr ())
gst_atomic_queue_peek Ptr AtomicQueue
queue'
    AtomicQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AtomicQueue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AtomicQueuePeekMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo AtomicQueuePeekMethodInfo AtomicQueue signature where
    overloadedMethod = atomicQueuePeek

#endif

-- method AtomicQueue::pop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "queue"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "AtomicQueue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstAtomicQueue" , 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 "gst_atomic_queue_pop" gst_atomic_queue_pop :: 
    Ptr AtomicQueue ->                      -- queue : TInterface (Name {namespace = "Gst", name = "AtomicQueue"})
    IO (Ptr ())

-- | Get the head element of the queue.
atomicQueuePop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AtomicQueue
    -- ^ /@queue@/: a t'GI.Gst.Structs.AtomicQueue.AtomicQueue'
    -> m (Ptr ())
    -- ^ __Returns:__ the head element of /@queue@/ or 'P.Nothing' when
    -- the queue is empty.
atomicQueuePop :: AtomicQueue -> m (Ptr ())
atomicQueuePop AtomicQueue
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 AtomicQueue
queue' <- AtomicQueue -> IO (Ptr AtomicQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AtomicQueue
queue
    Ptr ()
result <- Ptr AtomicQueue -> IO (Ptr ())
gst_atomic_queue_pop Ptr AtomicQueue
queue'
    AtomicQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AtomicQueue
queue
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data AtomicQueuePopMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo AtomicQueuePopMethodInfo AtomicQueue signature where
    overloadedMethod = atomicQueuePop

#endif

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

foreign import ccall "gst_atomic_queue_push" gst_atomic_queue_push :: 
    Ptr AtomicQueue ->                      -- queue : TInterface (Name {namespace = "Gst", name = "AtomicQueue"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO ()

-- | Append /@data@/ to the tail of the queue.
atomicQueuePush ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AtomicQueue
    -- ^ /@queue@/: a t'GI.Gst.Structs.AtomicQueue.AtomicQueue'
    -> Ptr ()
    -- ^ /@data@/: the data
    -> m ()
atomicQueuePush :: AtomicQueue -> Ptr () -> m ()
atomicQueuePush AtomicQueue
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 AtomicQueue
queue' <- AtomicQueue -> IO (Ptr AtomicQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AtomicQueue
queue
    Ptr AtomicQueue -> Ptr () -> IO ()
gst_atomic_queue_push Ptr AtomicQueue
queue' Ptr ()
data_
    AtomicQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AtomicQueue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AtomicQueuePushMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo AtomicQueuePushMethodInfo AtomicQueue signature where
    overloadedMethod = atomicQueuePush

#endif

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

foreign import ccall "gst_atomic_queue_ref" gst_atomic_queue_ref :: 
    Ptr AtomicQueue ->                      -- queue : TInterface (Name {namespace = "Gst", name = "AtomicQueue"})
    IO ()

-- | Increase the refcount of /@queue@/.
atomicQueueRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AtomicQueue
    -- ^ /@queue@/: a t'GI.Gst.Structs.AtomicQueue.AtomicQueue'
    -> m ()
atomicQueueRef :: AtomicQueue -> m ()
atomicQueueRef AtomicQueue
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 AtomicQueue
queue' <- AtomicQueue -> IO (Ptr AtomicQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AtomicQueue
queue
    Ptr AtomicQueue -> IO ()
gst_atomic_queue_ref Ptr AtomicQueue
queue'
    AtomicQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AtomicQueue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AtomicQueueRefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AtomicQueueRefMethodInfo AtomicQueue signature where
    overloadedMethod = atomicQueueRef

#endif

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

foreign import ccall "gst_atomic_queue_unref" gst_atomic_queue_unref :: 
    Ptr AtomicQueue ->                      -- queue : TInterface (Name {namespace = "Gst", name = "AtomicQueue"})
    IO ()

-- | Unref /@queue@/ and free the memory when the refcount reaches 0.
atomicQueueUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AtomicQueue
    -- ^ /@queue@/: a t'GI.Gst.Structs.AtomicQueue.AtomicQueue'
    -> m ()
atomicQueueUnref :: AtomicQueue -> m ()
atomicQueueUnref AtomicQueue
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 AtomicQueue
queue' <- AtomicQueue -> IO (Ptr AtomicQueue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AtomicQueue
queue
    Ptr AtomicQueue -> IO ()
gst_atomic_queue_unref Ptr AtomicQueue
queue'
    AtomicQueue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AtomicQueue
queue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AtomicQueueUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AtomicQueueUnrefMethodInfo AtomicQueue signature where
    overloadedMethod = atomicQueueUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAtomicQueueMethod (t :: Symbol) (o :: *) :: * where
    ResolveAtomicQueueMethod "length" o = AtomicQueueLengthMethodInfo
    ResolveAtomicQueueMethod "peek" o = AtomicQueuePeekMethodInfo
    ResolveAtomicQueueMethod "pop" o = AtomicQueuePopMethodInfo
    ResolveAtomicQueueMethod "push" o = AtomicQueuePushMethodInfo
    ResolveAtomicQueueMethod "ref" o = AtomicQueueRefMethodInfo
    ResolveAtomicQueueMethod "unref" o = AtomicQueueUnrefMethodInfo
    ResolveAtomicQueueMethod l o = O.MethodResolutionFailed l o

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

#endif