{-# 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.GLib.Structs.Cond.Cond' struct is an opaque data structure that represents a
-- condition. Threads can block on a t'GI.GLib.Structs.Cond.Cond' if they find a certain
-- condition to be false. If other threads change the state of this
-- condition they signal the t'GI.GLib.Structs.Cond.Cond', and that causes the waiting
-- threads to be woken up.
-- 
-- Consider the following example of a shared variable.  One or more
-- threads can wait for data to be published to the variable and when
-- another thread publishes the data, it can signal one of the waiting
-- threads to wake up to collect the data.
-- 
-- Here is an example for using GCond to block a thread until a condition
-- is satisfied:
-- 
-- === /C code/
-- >
-- >  gpointer current_data = NULL;
-- >  GMutex data_mutex;
-- >  GCond data_cond;
-- >
-- >  void
-- >  push_data (gpointer data)
-- >  {
-- >    g_mutex_lock (&data_mutex);
-- >    current_data = data;
-- >    g_cond_signal (&data_cond);
-- >    g_mutex_unlock (&data_mutex);
-- >  }
-- >
-- >  gpointer
-- >  pop_data (void)
-- >  {
-- >    gpointer data;
-- >
-- >    g_mutex_lock (&data_mutex);
-- >    while (!current_data)
-- >      g_cond_wait (&data_cond, &data_mutex);
-- >    data = current_data;
-- >    current_data = NULL;
-- >    g_mutex_unlock (&data_mutex);
-- >
-- >    return data;
-- >  }
-- 
-- Whenever a thread calls @/pop_data()/@ now, it will wait until
-- current_data is non-'P.Nothing', i.e. until some other thread
-- has called @/push_data()/@.
-- 
-- The example shows that use of a condition variable must always be
-- paired with a mutex.  Without the use of a mutex, there would be a
-- race between the check of /@currentData@/ by the while loop in
-- @/pop_data()/@ and waiting. Specifically, another thread could set
-- /@currentData@/ after the check, and signal the cond (with nobody
-- waiting on it) before the first thread goes to sleep. t'GI.GLib.Structs.Cond.Cond' is
-- specifically useful for its ability to release the mutex and go
-- to sleep atomically.
-- 
-- It is also important to use the 'GI.GLib.Structs.Cond.condWait' and 'GI.GLib.Structs.Cond.condWaitUntil'
-- functions only inside a loop which checks for the condition to be
-- true.  See 'GI.GLib.Structs.Cond.condWait' for an explanation of why the condition may
-- not be true even after it returns.
-- 
-- If a t'GI.GLib.Structs.Cond.Cond' is allocated in static storage then it can be used
-- without initialisation.  Otherwise, you should call 'GI.GLib.Structs.Cond.condInit'
-- on it and 'GI.GLib.Structs.Cond.condClear' when done.
-- 
-- A t'GI.GLib.Structs.Cond.Cond' should only be accessed via the g_cond_ functions.

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

module GI.GLib.Structs.Cond
    ( 

-- * Exported types
    Cond(..)                                ,
    newZeroCond                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [broadcast]("GI.GLib.Structs.Cond#g:method:broadcast"), [clear]("GI.GLib.Structs.Cond#g:method:clear"), [init]("GI.GLib.Structs.Cond#g:method:init"), [signal]("GI.GLib.Structs.Cond#g:method:signal"), [wait]("GI.GLib.Structs.Cond#g:method:wait"), [waitUntil]("GI.GLib.Structs.Cond#g:method:waitUntil").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveCondMethod                       ,
#endif

-- ** broadcast #method:broadcast#

#if defined(ENABLE_OVERLOADING)
    CondBroadcastMethodInfo                 ,
#endif
    condBroadcast                           ,


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    CondClearMethodInfo                     ,
#endif
    condClear                               ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    CondInitMethodInfo                      ,
#endif
    condInit                                ,


-- ** signal #method:signal#

#if defined(ENABLE_OVERLOADING)
    CondSignalMethodInfo                    ,
#endif
    condSignal                              ,


-- ** wait #method:wait#

#if defined(ENABLE_OVERLOADING)
    CondWaitMethodInfo                      ,
#endif
    condWait                                ,


-- ** waitUntil #method:waitUntil#

#if defined(ENABLE_OVERLOADING)
    CondWaitUntilMethodInfo                 ,
#endif
    condWaitUntil                           ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.GLib.Unions.Mutex as GLib.Mutex

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

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

instance BoxedPtr Cond where
    boxedPtrCopy :: Cond -> IO Cond
boxedPtrCopy = \Cond
p -> Cond -> (Ptr Cond -> IO Cond) -> IO Cond
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Cond
p (Int -> Ptr Cond -> IO (Ptr Cond)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr Cond -> IO (Ptr Cond))
-> (Ptr Cond -> IO Cond) -> Ptr Cond -> IO Cond
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr Cond -> Cond) -> Ptr Cond -> IO Cond
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr Cond -> Cond
Cond)
    boxedPtrFree :: Cond -> IO ()
boxedPtrFree = \Cond
x -> Cond -> (Ptr Cond -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr Cond
x Ptr Cond -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr Cond where
    boxedPtrCalloc :: IO (Ptr Cond)
boxedPtrCalloc = Int -> IO (Ptr Cond)
forall a. Int -> IO (Ptr a)
callocBytes Int
16


-- | Construct a `Cond` struct initialized to zero.
newZeroCond :: MonadIO m => m Cond
newZeroCond :: forall (m :: * -> *). MonadIO m => m Cond
newZeroCond = IO Cond -> m Cond
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Cond -> m Cond) -> IO Cond -> m Cond
forall a b. (a -> b) -> a -> b
$ IO (Ptr Cond)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr Cond) -> (Ptr Cond -> IO Cond) -> IO Cond
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Cond -> Cond) -> Ptr Cond -> IO Cond
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Cond -> Cond
Cond

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



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

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

foreign import ccall "g_cond_broadcast" g_cond_broadcast :: 
    Ptr Cond ->                             -- cond : TInterface (Name {namespace = "GLib", name = "Cond"})
    IO ()

-- | If threads are waiting for /@cond@/, all of them are unblocked.
-- If no threads are waiting for /@cond@/, this function has no effect.
-- It is good practice to lock the same mutex as the waiting threads
-- while calling this function, though not required.
condBroadcast ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Cond
    -- ^ /@cond@/: a t'GI.GLib.Structs.Cond.Cond'
    -> m ()
condBroadcast :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Cond -> m ()
condBroadcast Cond
cond = 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 Cond
cond' <- Cond -> IO (Ptr Cond)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Cond
cond
    Ptr Cond -> IO ()
g_cond_broadcast Ptr Cond
cond'
    Cond -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Cond
cond
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CondBroadcastMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod CondBroadcastMethodInfo Cond signature where
    overloadedMethod = condBroadcast

instance O.OverloadedMethodInfo CondBroadcastMethodInfo Cond where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Cond.condBroadcast",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Cond.html#v:condBroadcast"
        }


#endif

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

foreign import ccall "g_cond_clear" g_cond_clear :: 
    Ptr Cond ->                             -- cond : TInterface (Name {namespace = "GLib", name = "Cond"})
    IO ()

-- | Frees the resources allocated to a t'GI.GLib.Structs.Cond.Cond' with 'GI.GLib.Structs.Cond.condInit'.
-- 
-- This function should not be used with a t'GI.GLib.Structs.Cond.Cond' that has been
-- statically allocated.
-- 
-- Calling 'GI.GLib.Structs.Cond.condClear' for a t'GI.GLib.Structs.Cond.Cond' on which threads are
-- blocking leads to undefined behaviour.
-- 
-- /Since: 2.32/
condClear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Cond
    -- ^ /@cond@/: an initialised t'GI.GLib.Structs.Cond.Cond'
    -> m ()
condClear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Cond -> m ()
condClear Cond
cond = 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 Cond
cond' <- Cond -> IO (Ptr Cond)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Cond
cond
    Ptr Cond -> IO ()
g_cond_clear Ptr Cond
cond'
    Cond -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Cond
cond
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CondClearMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod CondClearMethodInfo Cond signature where
    overloadedMethod = condClear

instance O.OverloadedMethodInfo CondClearMethodInfo Cond where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Cond.condClear",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Cond.html#v:condClear"
        }


#endif

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

foreign import ccall "g_cond_init" g_cond_init :: 
    Ptr Cond ->                             -- cond : TInterface (Name {namespace = "GLib", name = "Cond"})
    IO ()

-- | Initialises a t'GI.GLib.Structs.Cond.Cond' so that it can be used.
-- 
-- This function is useful to initialise a t'GI.GLib.Structs.Cond.Cond' that has been
-- allocated as part of a larger structure.  It is not necessary to
-- initialise a t'GI.GLib.Structs.Cond.Cond' that has been statically allocated.
-- 
-- To undo the effect of 'GI.GLib.Structs.Cond.condInit' when a t'GI.GLib.Structs.Cond.Cond' is no longer
-- needed, use 'GI.GLib.Structs.Cond.condClear'.
-- 
-- Calling 'GI.GLib.Structs.Cond.condInit' on an already-initialised t'GI.GLib.Structs.Cond.Cond' leads
-- to undefined behaviour.
-- 
-- /Since: 2.32/
condInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Cond
    -- ^ /@cond@/: an uninitialized t'GI.GLib.Structs.Cond.Cond'
    -> m ()
condInit :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Cond -> m ()
condInit Cond
cond = 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 Cond
cond' <- Cond -> IO (Ptr Cond)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Cond
cond
    Ptr Cond -> IO ()
g_cond_init Ptr Cond
cond'
    Cond -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Cond
cond
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CondInitMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod CondInitMethodInfo Cond signature where
    overloadedMethod = condInit

instance O.OverloadedMethodInfo CondInitMethodInfo Cond where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Cond.condInit",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Cond.html#v:condInit"
        }


#endif

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

foreign import ccall "g_cond_signal" g_cond_signal :: 
    Ptr Cond ->                             -- cond : TInterface (Name {namespace = "GLib", name = "Cond"})
    IO ()

-- | If threads are waiting for /@cond@/, at least one of them is unblocked.
-- If no threads are waiting for /@cond@/, this function has no effect.
-- It is good practice to hold the same lock as the waiting thread
-- while calling this function, though not required.
condSignal ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Cond
    -- ^ /@cond@/: a t'GI.GLib.Structs.Cond.Cond'
    -> m ()
condSignal :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Cond -> m ()
condSignal Cond
cond = 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 Cond
cond' <- Cond -> IO (Ptr Cond)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Cond
cond
    Ptr Cond -> IO ()
g_cond_signal Ptr Cond
cond'
    Cond -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Cond
cond
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CondSignalMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod CondSignalMethodInfo Cond signature where
    overloadedMethod = condSignal

instance O.OverloadedMethodInfo CondSignalMethodInfo Cond where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Cond.condSignal",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Cond.html#v:condSignal"
        }


#endif

-- method Cond::wait
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cond"
--           , argType = TInterface Name { namespace = "GLib" , name = "Cond" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCond" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mutex"
--           , argType = TInterface Name { namespace = "GLib" , name = "Mutex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMutex that is currently locked"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cond_wait" g_cond_wait :: 
    Ptr Cond ->                             -- cond : TInterface (Name {namespace = "GLib", name = "Cond"})
    Ptr GLib.Mutex.Mutex ->                 -- mutex : TInterface (Name {namespace = "GLib", name = "Mutex"})
    IO ()

-- | Atomically releases /@mutex@/ and waits until /@cond@/ is signalled.
-- When this function returns, /@mutex@/ is locked again and owned by the
-- calling thread.
-- 
-- When using condition variables, it is possible that a spurious wakeup
-- may occur (ie: 'GI.GLib.Structs.Cond.condWait' returns even though 'GI.GLib.Structs.Cond.condSignal' was
-- not called).  It\'s also possible that a stolen wakeup may occur.
-- This is when 'GI.GLib.Structs.Cond.condSignal' is called, but another thread acquires
-- /@mutex@/ before this thread and modifies the state of the program in
-- such a way that when 'GI.GLib.Structs.Cond.condWait' is able to return, the expected
-- condition is no longer met.
-- 
-- For this reason, 'GI.GLib.Structs.Cond.condWait' must always be used in a loop.  See
-- the documentation for t'GI.GLib.Structs.Cond.Cond' for a complete example.
condWait ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Cond
    -- ^ /@cond@/: a t'GI.GLib.Structs.Cond.Cond'
    -> GLib.Mutex.Mutex
    -- ^ /@mutex@/: a t'GI.GLib.Unions.Mutex.Mutex' that is currently locked
    -> m ()
condWait :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Cond -> Mutex -> m ()
condWait Cond
cond Mutex
mutex = 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 Cond
cond' <- Cond -> IO (Ptr Cond)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Cond
cond
    Ptr Mutex
mutex' <- Mutex -> IO (Ptr Mutex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Mutex
mutex
    Ptr Cond -> Ptr Mutex -> IO ()
g_cond_wait Ptr Cond
cond' Ptr Mutex
mutex'
    Cond -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Cond
cond
    Mutex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Mutex
mutex
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CondWaitMethodInfo
instance (signature ~ (GLib.Mutex.Mutex -> m ()), MonadIO m) => O.OverloadedMethod CondWaitMethodInfo Cond signature where
    overloadedMethod = condWait

instance O.OverloadedMethodInfo CondWaitMethodInfo Cond where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Cond.condWait",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Cond.html#v:condWait"
        }


#endif

-- method Cond::wait_until
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cond"
--           , argType = TInterface Name { namespace = "GLib" , name = "Cond" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCond" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mutex"
--           , argType = TInterface Name { namespace = "GLib" , name = "Mutex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMutex that is currently locked"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_time"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the monotonic time to wait until"
--                 , 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_cond_wait_until" g_cond_wait_until :: 
    Ptr Cond ->                             -- cond : TInterface (Name {namespace = "GLib", name = "Cond"})
    Ptr GLib.Mutex.Mutex ->                 -- mutex : TInterface (Name {namespace = "GLib", name = "Mutex"})
    Int64 ->                                -- end_time : TBasicType TInt64
    IO CInt

-- | Waits until either /@cond@/ is signalled or /@endTime@/ has passed.
-- 
-- As with 'GI.GLib.Structs.Cond.condWait' it is possible that a spurious or stolen wakeup
-- could occur.  For that reason, waiting on a condition variable should
-- always be in a loop, based on an explicitly-checked predicate.
-- 
-- 'P.True' is returned if the condition variable was signalled (or in the
-- case of a spurious wakeup).  'P.False' is returned if /@endTime@/ has
-- passed.
-- 
-- The following code shows how to correctly perform a timed wait on a
-- condition variable (extending the example presented in the
-- documentation for t'GI.GLib.Structs.Cond.Cond'):
-- 
-- 
-- === /C code/
-- >
-- >gpointer
-- >pop_data_timed (void)
-- >{
-- >  gint64 end_time;
-- >  gpointer data;
-- >
-- >  g_mutex_lock (&data_mutex);
-- >
-- >  end_time = g_get_monotonic_time () + 5 * G_TIME_SPAN_SECOND;
-- >  while (!current_data)
-- >    if (!g_cond_wait_until (&data_cond, &data_mutex, end_time))
-- >      {
-- >        // timeout has passed.
-- >        g_mutex_unlock (&data_mutex);
-- >        return NULL;
-- >      }
-- >
-- >  // there is data for us
-- >  data = current_data;
-- >  current_data = NULL;
-- >
-- >  g_mutex_unlock (&data_mutex);
-- >
-- >  return data;
-- >}
-- 
-- 
-- Notice that the end time is calculated once, before entering the
-- loop and reused.  This is the motivation behind the use of absolute
-- time on this API -- if a relative time of 5 seconds were passed
-- directly to the call and a spurious wakeup occurred, the program would
-- have to start over waiting again (which would lead to a total wait
-- time of more than 5 seconds).
-- 
-- /Since: 2.32/
condWaitUntil ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Cond
    -- ^ /@cond@/: a t'GI.GLib.Structs.Cond.Cond'
    -> GLib.Mutex.Mutex
    -- ^ /@mutex@/: a t'GI.GLib.Unions.Mutex.Mutex' that is currently locked
    -> Int64
    -- ^ /@endTime@/: the monotonic time to wait until
    -> m Bool
    -- ^ __Returns:__ 'P.True' on a signal, 'P.False' on a timeout
condWaitUntil :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Cond -> Mutex -> Int64 -> m Bool
condWaitUntil Cond
cond Mutex
mutex Int64
endTime = 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 Cond
cond' <- Cond -> IO (Ptr Cond)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Cond
cond
    Ptr Mutex
mutex' <- Mutex -> IO (Ptr Mutex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Mutex
mutex
    CInt
result <- Ptr Cond -> Ptr Mutex -> Int64 -> IO CInt
g_cond_wait_until Ptr Cond
cond' Ptr Mutex
mutex' Int64
endTime
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Cond -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Cond
cond
    Mutex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Mutex
mutex
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data CondWaitUntilMethodInfo
instance (signature ~ (GLib.Mutex.Mutex -> Int64 -> m Bool), MonadIO m) => O.OverloadedMethod CondWaitUntilMethodInfo Cond signature where
    overloadedMethod = condWaitUntil

instance O.OverloadedMethodInfo CondWaitUntilMethodInfo Cond where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Cond.condWaitUntil",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Cond.html#v:condWaitUntil"
        }


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveCondMethod (t :: Symbol) (o :: *) :: * where
    ResolveCondMethod "broadcast" o = CondBroadcastMethodInfo
    ResolveCondMethod "clear" o = CondClearMethodInfo
    ResolveCondMethod "init" o = CondInitMethodInfo
    ResolveCondMethod "signal" o = CondSignalMethodInfo
    ResolveCondMethod "wait" o = CondWaitMethodInfo
    ResolveCondMethod "waitUntil" o = CondWaitUntilMethodInfo
    ResolveCondMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveCondMethod t Cond, O.OverloadedMethod info Cond p, R.HasField t Cond p) => R.HasField t Cond p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveCondMethod t Cond, O.OverloadedMethodInfo info Cond) => OL.IsLabel t (O.MethodProxy info Cond) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif