{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.RecMutex
    ( 
    RecMutex(..)                            ,
    newZeroRecMutex                         ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveRecMutexMethod                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    RecMutexClearMethodInfo                 ,
#endif
    recMutexClear                           ,
#if defined(ENABLE_OVERLOADING)
    RecMutexInitMethodInfo                  ,
#endif
    recMutexInit                            ,
#if defined(ENABLE_OVERLOADING)
    RecMutexLockMethodInfo                  ,
#endif
    recMutexLock                            ,
#if defined(ENABLE_OVERLOADING)
    RecMutexTrylockMethodInfo               ,
#endif
    recMutexTrylock                         ,
#if defined(ENABLE_OVERLOADING)
    RecMutexUnlockMethodInfo                ,
#endif
    recMutexUnlock                          ,
    ) 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.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
#else
#endif
newtype RecMutex = RecMutex (SP.ManagedPtr RecMutex)
    deriving (RecMutex -> RecMutex -> Bool
(RecMutex -> RecMutex -> Bool)
-> (RecMutex -> RecMutex -> Bool) -> Eq RecMutex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecMutex -> RecMutex -> Bool
== :: RecMutex -> RecMutex -> Bool
$c/= :: RecMutex -> RecMutex -> Bool
/= :: RecMutex -> RecMutex -> Bool
Eq)
instance SP.ManagedPtrNewtype RecMutex where
    toManagedPtr :: RecMutex -> ManagedPtr RecMutex
toManagedPtr (RecMutex ManagedPtr RecMutex
p) = ManagedPtr RecMutex
p
instance BoxedPtr RecMutex where
    boxedPtrCopy :: RecMutex -> IO RecMutex
boxedPtrCopy = \RecMutex
p -> RecMutex -> (Ptr RecMutex -> IO RecMutex) -> IO RecMutex
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RecMutex
p (Int -> Ptr RecMutex -> IO (Ptr RecMutex)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr RecMutex -> IO (Ptr RecMutex))
-> (Ptr RecMutex -> IO RecMutex) -> Ptr RecMutex -> IO RecMutex
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr RecMutex -> RecMutex) -> Ptr RecMutex -> IO RecMutex
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr RecMutex -> RecMutex
RecMutex)
    boxedPtrFree :: RecMutex -> IO ()
boxedPtrFree = \RecMutex
x -> RecMutex -> (Ptr RecMutex -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr RecMutex
x Ptr RecMutex -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr RecMutex where
    boxedPtrCalloc :: IO (Ptr RecMutex)
boxedPtrCalloc = Int -> IO (Ptr RecMutex)
forall a. Int -> IO (Ptr a)
callocBytes Int
16
newZeroRecMutex :: MonadIO m => m RecMutex
newZeroRecMutex :: forall (m :: * -> *). MonadIO m => m RecMutex
newZeroRecMutex = IO RecMutex -> m RecMutex
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RecMutex -> m RecMutex) -> IO RecMutex -> m RecMutex
forall a b. (a -> b) -> a -> b
$ IO (Ptr RecMutex)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr RecMutex) -> (Ptr RecMutex -> IO RecMutex) -> IO RecMutex
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr RecMutex -> RecMutex) -> Ptr RecMutex -> IO RecMutex
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr RecMutex -> RecMutex
RecMutex
instance tag ~ 'AttrSet => Constructible RecMutex tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr RecMutex -> RecMutex)
-> [AttrOp RecMutex tag] -> m RecMutex
new ManagedPtr RecMutex -> RecMutex
_ [AttrOp RecMutex tag]
attrs = do
        RecMutex
o <- m RecMutex
forall (m :: * -> *). MonadIO m => m RecMutex
newZeroRecMutex
        RecMutex -> [AttrOp RecMutex 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set RecMutex
o [AttrOp RecMutex tag]
[AttrOp RecMutex 'AttrSet]
attrs
        RecMutex -> m RecMutex
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return RecMutex
o
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RecMutex
type instance O.AttributeList RecMutex = RecMutexAttributeList
type RecMutexAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "g_rec_mutex_clear" g_rec_mutex_clear :: 
    Ptr RecMutex ->                         
    IO ()
recMutexClear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecMutex
    
    -> m ()
recMutexClear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => RecMutex -> m ()
recMutexClear RecMutex
recMutex = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecMutex
recMutex' <- RecMutex -> IO (Ptr RecMutex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecMutex
recMutex
    Ptr RecMutex -> IO ()
g_rec_mutex_clear Ptr RecMutex
recMutex'
    RecMutex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecMutex
recMutex
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RecMutexClearMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RecMutexClearMethodInfo RecMutex signature where
    overloadedMethod = recMutexClear
instance O.OverloadedMethodInfo RecMutexClearMethodInfo RecMutex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.RecMutex.recMutexClear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-RecMutex.html#v:recMutexClear"
        })
#endif
foreign import ccall "g_rec_mutex_init" g_rec_mutex_init :: 
    Ptr RecMutex ->                         
    IO ()
recMutexInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecMutex
    
    -> m ()
recMutexInit :: forall (m :: * -> *). (HasCallStack, MonadIO m) => RecMutex -> m ()
recMutexInit RecMutex
recMutex = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecMutex
recMutex' <- RecMutex -> IO (Ptr RecMutex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecMutex
recMutex
    Ptr RecMutex -> IO ()
g_rec_mutex_init Ptr RecMutex
recMutex'
    RecMutex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecMutex
recMutex
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RecMutexInitMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RecMutexInitMethodInfo RecMutex signature where
    overloadedMethod = recMutexInit
instance O.OverloadedMethodInfo RecMutexInitMethodInfo RecMutex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.RecMutex.recMutexInit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-RecMutex.html#v:recMutexInit"
        })
#endif
foreign import ccall "g_rec_mutex_lock" g_rec_mutex_lock :: 
    Ptr RecMutex ->                         
    IO ()
recMutexLock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecMutex
    
    -> m ()
recMutexLock :: forall (m :: * -> *). (HasCallStack, MonadIO m) => RecMutex -> m ()
recMutexLock RecMutex
recMutex = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecMutex
recMutex' <- RecMutex -> IO (Ptr RecMutex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecMutex
recMutex
    Ptr RecMutex -> IO ()
g_rec_mutex_lock Ptr RecMutex
recMutex'
    RecMutex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecMutex
recMutex
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RecMutexLockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RecMutexLockMethodInfo RecMutex signature where
    overloadedMethod = recMutexLock
instance O.OverloadedMethodInfo RecMutexLockMethodInfo RecMutex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.RecMutex.recMutexLock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-RecMutex.html#v:recMutexLock"
        })
#endif
foreign import ccall "g_rec_mutex_trylock" g_rec_mutex_trylock :: 
    Ptr RecMutex ->                         
    IO CInt
recMutexTrylock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecMutex
    
    -> m Bool
    
recMutexTrylock :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecMutex -> m Bool
recMutexTrylock RecMutex
recMutex = IO Bool -> m Bool
forall a. IO a -> m a
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 RecMutex
recMutex' <- RecMutex -> IO (Ptr RecMutex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecMutex
recMutex
    CInt
result <- Ptr RecMutex -> IO CInt
g_rec_mutex_trylock Ptr RecMutex
recMutex'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    RecMutex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecMutex
recMutex
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data RecMutexTrylockMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod RecMutexTrylockMethodInfo RecMutex signature where
    overloadedMethod = recMutexTrylock
instance O.OverloadedMethodInfo RecMutexTrylockMethodInfo RecMutex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.RecMutex.recMutexTrylock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-RecMutex.html#v:recMutexTrylock"
        })
#endif
foreign import ccall "g_rec_mutex_unlock" g_rec_mutex_unlock :: 
    Ptr RecMutex ->                         
    IO ()
recMutexUnlock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecMutex
    
    -> m ()
recMutexUnlock :: forall (m :: * -> *). (HasCallStack, MonadIO m) => RecMutex -> m ()
recMutexUnlock RecMutex
recMutex = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecMutex
recMutex' <- RecMutex -> IO (Ptr RecMutex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecMutex
recMutex
    Ptr RecMutex -> IO ()
g_rec_mutex_unlock Ptr RecMutex
recMutex'
    RecMutex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecMutex
recMutex
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RecMutexUnlockMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RecMutexUnlockMethodInfo RecMutex signature where
    overloadedMethod = recMutexUnlock
instance O.OverloadedMethodInfo RecMutexUnlockMethodInfo RecMutex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.RecMutex.recMutexUnlock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-RecMutex.html#v:recMutexUnlock"
        })
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveRecMutexMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveRecMutexMethod "clear" o = RecMutexClearMethodInfo
    ResolveRecMutexMethod "init" o = RecMutexInitMethodInfo
    ResolveRecMutexMethod "lock" o = RecMutexLockMethodInfo
    ResolveRecMutexMethod "trylock" o = RecMutexTrylockMethodInfo
    ResolveRecMutexMethod "unlock" o = RecMutexUnlockMethodInfo
    ResolveRecMutexMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRecMutexMethod t RecMutex, O.OverloadedMethod info RecMutex p) => OL.IsLabel t (RecMutex -> 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 ~ ResolveRecMutexMethod t RecMutex, O.OverloadedMethod info RecMutex p, R.HasField t RecMutex p) => R.HasField t RecMutex p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveRecMutexMethod t RecMutex, O.OverloadedMethodInfo info RecMutex) => OL.IsLabel t (O.MethodProxy info RecMutex) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif