{-# 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.Thread.Thread' struct represents a running thread. This struct
-- is returned by @/g_thread_new()/@ or @/g_thread_try_new()/@. You can
-- obtain the t'GI.GLib.Structs.Thread.Thread' struct representing the current thread by
-- calling 'GI.GLib.Functions.threadSelf'.
-- 
-- GThread is refcounted, see 'GI.GLib.Structs.Thread.threadRef' and 'GI.GLib.Structs.Thread.threadUnref'.
-- The thread represented by it holds a reference while it is running,
-- and 'GI.GLib.Structs.Thread.threadJoin' consumes the reference that it is given, so
-- it is normally not necessary to manage GThread references
-- explicitly.
-- 
-- The structure is opaque -- none of its fields may be directly
-- accessed.

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

module GI.GLib.Structs.Thread
    ( 

-- * Exported types
    Thread(..)                              ,
    noThread                                ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveThreadMethod                     ,
#endif


-- ** errorQuark #method:errorQuark#

    threadErrorQuark                        ,


-- ** exit #method:exit#

    threadExit                              ,


-- ** join #method:join#

#if defined(ENABLE_OVERLOADING)
    ThreadJoinMethodInfo                    ,
#endif
    threadJoin                              ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    ThreadRefMethodInfo                     ,
#endif
    threadRef                               ,


-- ** self #method:self#

    threadSelf                              ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    ThreadUnrefMethodInfo                   ,
#endif
    threadUnref                             ,


-- ** yield #method:yield#

    threadYield                             ,




    ) 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


-- | Memory-managed wrapper type.
newtype Thread = Thread (ManagedPtr Thread)
    deriving (Thread -> Thread -> Bool
(Thread -> Thread -> Bool)
-> (Thread -> Thread -> Bool) -> Eq Thread
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Thread -> Thread -> Bool
$c/= :: Thread -> Thread -> Bool
== :: Thread -> Thread -> Bool
$c== :: Thread -> Thread -> Bool
Eq)
foreign import ccall "g_thread_get_type" c_g_thread_get_type :: 
    IO GType

instance BoxedObject Thread where
    boxedType :: Thread -> IO GType
boxedType _ = IO GType
c_g_thread_get_type

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

-- | A convenience alias for `Nothing` :: `Maybe` `Thread`.
noThread :: Maybe Thread
noThread :: Maybe Thread
noThread = Maybe Thread
forall a. Maybe a
Nothing


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

-- method Thread::join
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "thread"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Thread" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThread" , 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_thread_join" g_thread_join :: 
    Ptr Thread ->                           -- thread : TInterface (Name {namespace = "GLib", name = "Thread"})
    IO (Ptr ())

-- | Waits until /@thread@/ finishes, i.e. the function /@func@/, as
-- given to @/g_thread_new()/@, returns or 'GI.GLib.Functions.threadExit' is called.
-- If /@thread@/ has already terminated, then 'GI.GLib.Structs.Thread.threadJoin'
-- returns immediately.
-- 
-- Any thread can wait for any other thread by calling 'GI.GLib.Structs.Thread.threadJoin',
-- not just its \'creator\'. Calling 'GI.GLib.Structs.Thread.threadJoin' from multiple threads
-- for the same /@thread@/ leads to undefined behaviour.
-- 
-- The value returned by /@func@/ or given to 'GI.GLib.Functions.threadExit' is
-- returned by this function.
-- 
-- 'GI.GLib.Structs.Thread.threadJoin' consumes the reference to the passed-in /@thread@/.
-- This will usually cause the t'GI.GLib.Structs.Thread.Thread' struct and associated resources
-- to be freed. Use 'GI.GLib.Structs.Thread.threadRef' to obtain an extra reference if you
-- want to keep the GThread alive beyond the 'GI.GLib.Structs.Thread.threadJoin' call.
threadJoin ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Thread
    -- ^ /@thread@/: a t'GI.GLib.Structs.Thread.Thread'
    -> m (Ptr ())
    -- ^ __Returns:__ the return value of the thread
threadJoin :: Thread -> m (Ptr ())
threadJoin thread :: Thread
thread = 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 Thread
thread' <- Thread -> IO (Ptr Thread)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Thread
thread
    Ptr ()
result <- Ptr Thread -> IO (Ptr ())
g_thread_join Ptr Thread
thread'
    Thread -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Thread
thread
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data ThreadJoinMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo ThreadJoinMethodInfo Thread signature where
    overloadedMethod = threadJoin

#endif

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

foreign import ccall "g_thread_ref" g_thread_ref :: 
    Ptr Thread ->                           -- thread : TInterface (Name {namespace = "GLib", name = "Thread"})
    IO (Ptr Thread)

-- | Increase the reference count on /@thread@/.
-- 
-- /Since: 2.32/
threadRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Thread
    -- ^ /@thread@/: a t'GI.GLib.Structs.Thread.Thread'
    -> m Thread
    -- ^ __Returns:__ a new reference to /@thread@/
threadRef :: Thread -> m Thread
threadRef thread :: Thread
thread = IO Thread -> m Thread
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Thread -> m Thread) -> IO Thread -> m Thread
forall a b. (a -> b) -> a -> b
$ do
    Ptr Thread
thread' <- Thread -> IO (Ptr Thread)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Thread
thread
    Ptr Thread
result <- Ptr Thread -> IO (Ptr Thread)
g_thread_ref Ptr Thread
thread'
    Text -> Ptr Thread -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "threadRef" Ptr Thread
result
    Thread
result' <- ((ManagedPtr Thread -> Thread) -> Ptr Thread -> IO Thread
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Thread -> Thread
Thread) Ptr Thread
result
    Thread -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Thread
thread
    Thread -> IO Thread
forall (m :: * -> *) a. Monad m => a -> m a
return Thread
result'

#if defined(ENABLE_OVERLOADING)
data ThreadRefMethodInfo
instance (signature ~ (m Thread), MonadIO m) => O.MethodInfo ThreadRefMethodInfo Thread signature where
    overloadedMethod = threadRef

#endif

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

foreign import ccall "g_thread_unref" g_thread_unref :: 
    Ptr Thread ->                           -- thread : TInterface (Name {namespace = "GLib", name = "Thread"})
    IO ()

-- | Decrease the reference count on /@thread@/, possibly freeing all
-- resources associated with it.
-- 
-- Note that each thread holds a reference to its t'GI.GLib.Structs.Thread.Thread' while
-- it is running, so it is safe to drop your own reference to it
-- if you don\'t need it anymore.
-- 
-- /Since: 2.32/
threadUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Thread
    -- ^ /@thread@/: a t'GI.GLib.Structs.Thread.Thread'
    -> m ()
threadUnref :: Thread -> m ()
threadUnref thread :: Thread
thread = 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 Thread
thread' <- Thread -> IO (Ptr Thread)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Thread
thread
    Ptr Thread -> IO ()
g_thread_unref Ptr Thread
thread'
    Thread -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Thread
thread
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ThreadUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ThreadUnrefMethodInfo Thread signature where
    overloadedMethod = threadUnref

#endif

-- method Thread::error_quark
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TBasicType TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_error_quark" g_thread_error_quark :: 
    IO Word32

-- | /No description available in the introspection data./
threadErrorQuark ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Word32
threadErrorQuark :: m Word32
threadErrorQuark  = 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
    Word32
result <- IO Word32
g_thread_error_quark
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Thread::exit
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "retval"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the return value of this thread"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_exit" g_thread_exit :: 
    Ptr () ->                               -- retval : TBasicType TPtr
    IO ()

-- | Terminates the current thread.
-- 
-- If another thread is waiting for us using 'GI.GLib.Structs.Thread.threadJoin' then the
-- waiting thread will be woken up and get /@retval@/ as the return value
-- of 'GI.GLib.Structs.Thread.threadJoin'.
-- 
-- Calling 'GI.GLib.Functions.threadExit' with a parameter /@retval@/ is equivalent to
-- returning /@retval@/ from the function /@func@/, as given to @/g_thread_new()/@.
-- 
-- You must only call 'GI.GLib.Functions.threadExit' from a thread that you created
-- yourself with @/g_thread_new()/@ or related APIs. You must not call
-- this function from a thread created with another threading library
-- or or from within a t'GI.GLib.Structs.ThreadPool.ThreadPool'.
threadExit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Ptr ()
    -- ^ /@retval@/: the return value of this thread
    -> m ()
threadExit :: Ptr () -> m ()
threadExit retval :: Ptr ()
retval = 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 () -> IO ()
g_thread_exit Ptr ()
retval
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Thread::self
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Thread" })
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_self" g_thread_self :: 
    IO (Ptr Thread)

-- | This function returns the t'GI.GLib.Structs.Thread.Thread' corresponding to the
-- current thread. Note that this function does not increase
-- the reference count of the returned struct.
-- 
-- This function will return a t'GI.GLib.Structs.Thread.Thread' even for threads that
-- were not created by GLib (i.e. those created by other threading
-- APIs). This may be useful for thread identification purposes
-- (i.e. comparisons) but you must not use GLib functions (such
-- as 'GI.GLib.Structs.Thread.threadJoin') on these threads.
threadSelf ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Thread
    -- ^ __Returns:__ the t'GI.GLib.Structs.Thread.Thread' representing the current thread
threadSelf :: m Thread
threadSelf  = IO Thread -> m Thread
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Thread -> m Thread) -> IO Thread -> m Thread
forall a b. (a -> b) -> a -> b
$ do
    Ptr Thread
result <- IO (Ptr Thread)
g_thread_self
    Text -> Ptr Thread -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "threadSelf" Ptr Thread
result
    Thread
result' <- ((ManagedPtr Thread -> Thread) -> Ptr Thread -> IO Thread
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Thread -> Thread
Thread) Ptr Thread
result
    Thread -> IO Thread
forall (m :: * -> *) a. Monad m => a -> m a
return Thread
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Thread::yield
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_yield" g_thread_yield :: 
    IO ()

-- | Causes the calling thread to voluntarily relinquish the CPU, so
-- that other threads can run.
-- 
-- This function is often used as a method to make busy wait less evil.
threadYield ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ()
threadYield :: m ()
threadYield  = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    IO ()
g_thread_yield
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveThreadMethod (t :: Symbol) (o :: *) :: * where
    ResolveThreadMethod "join" o = ThreadJoinMethodInfo
    ResolveThreadMethod "ref" o = ThreadRefMethodInfo
    ResolveThreadMethod "unref" o = ThreadUnrefMethodInfo
    ResolveThreadMethod l o = O.MethodResolutionFailed l o

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

#endif