{-# 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.ThreadPool.ThreadPool' struct represents a thread pool. It has three
-- public read-only members, but the underlying struct is bigger,
-- so you must not copy this struct.

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

module GI.GLib.Structs.ThreadPool
    ( 

-- * Exported types
    ThreadPool(..)                          ,
    newZeroThreadPool                       ,
    noThreadPool                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveThreadPoolMethod                 ,
#endif


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    ThreadPoolFreeMethodInfo                ,
#endif
    threadPoolFree                          ,


-- ** getMaxIdleTime #method:getMaxIdleTime#

    threadPoolGetMaxIdleTime                ,


-- ** getMaxThreads #method:getMaxThreads#

#if defined(ENABLE_OVERLOADING)
    ThreadPoolGetMaxThreadsMethodInfo       ,
#endif
    threadPoolGetMaxThreads                 ,


-- ** getMaxUnusedThreads #method:getMaxUnusedThreads#

    threadPoolGetMaxUnusedThreads           ,


-- ** getNumThreads #method:getNumThreads#

#if defined(ENABLE_OVERLOADING)
    ThreadPoolGetNumThreadsMethodInfo       ,
#endif
    threadPoolGetNumThreads                 ,


-- ** getNumUnusedThreads #method:getNumUnusedThreads#

    threadPoolGetNumUnusedThreads           ,


-- ** moveToFront #method:moveToFront#

#if defined(ENABLE_OVERLOADING)
    ThreadPoolMoveToFrontMethodInfo         ,
#endif
    threadPoolMoveToFront                   ,


-- ** push #method:push#

#if defined(ENABLE_OVERLOADING)
    ThreadPoolPushMethodInfo                ,
#endif
    threadPoolPush                          ,


-- ** setMaxIdleTime #method:setMaxIdleTime#

    threadPoolSetMaxIdleTime                ,


-- ** setMaxThreads #method:setMaxThreads#

#if defined(ENABLE_OVERLOADING)
    ThreadPoolSetMaxThreadsMethodInfo       ,
#endif
    threadPoolSetMaxThreads                 ,


-- ** setMaxUnusedThreads #method:setMaxUnusedThreads#

    threadPoolSetMaxUnusedThreads           ,


-- ** stopUnusedThreads #method:stopUnusedThreads#

    threadPoolStopUnusedThreads             ,


-- ** unprocessed #method:unprocessed#

#if defined(ENABLE_OVERLOADING)
    ThreadPoolUnprocessedMethodInfo         ,
#endif
    threadPoolUnprocessed                   ,




 -- * Properties
-- ** exclusive #attr:exclusive#
-- | are all threads exclusive to this pool

    getThreadPoolExclusive                  ,
    setThreadPoolExclusive                  ,
#if defined(ENABLE_OVERLOADING)
    threadPool_exclusive                    ,
#endif


-- ** func #attr:func#
-- | the function to execute in the threads of this pool

    clearThreadPoolFunc                     ,
    getThreadPoolFunc                       ,
    setThreadPoolFunc                       ,
#if defined(ENABLE_OVERLOADING)
    threadPool_func                         ,
#endif


-- ** userData #attr:userData#
-- | the user data for the threads of this pool

    clearThreadPoolUserData                 ,
    getThreadPoolUserData                   ,
    setThreadPoolUserData                   ,
#if defined(ENABLE_OVERLOADING)
    threadPool_userData                     ,
#endif




    ) 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 ThreadPool = ThreadPool (ManagedPtr ThreadPool)
    deriving (ThreadPool -> ThreadPool -> Bool
(ThreadPool -> ThreadPool -> Bool)
-> (ThreadPool -> ThreadPool -> Bool) -> Eq ThreadPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThreadPool -> ThreadPool -> Bool
$c/= :: ThreadPool -> ThreadPool -> Bool
== :: ThreadPool -> ThreadPool -> Bool
$c== :: ThreadPool -> ThreadPool -> Bool
Eq)
instance WrappedPtr ThreadPool where
    wrappedPtrCalloc :: IO (Ptr ThreadPool)
wrappedPtrCalloc = Int -> IO (Ptr ThreadPool)
forall a. Int -> IO (Ptr a)
callocBytes 24
    wrappedPtrCopy :: ThreadPool -> IO ThreadPool
wrappedPtrCopy = \p :: ThreadPool
p -> ThreadPool -> (Ptr ThreadPool -> IO ThreadPool) -> IO ThreadPool
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ThreadPool
p (Int -> Ptr ThreadPool -> IO (Ptr ThreadPool)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 24 (Ptr ThreadPool -> IO (Ptr ThreadPool))
-> (Ptr ThreadPool -> IO ThreadPool)
-> Ptr ThreadPool
-> IO ThreadPool
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ThreadPool -> ThreadPool)
-> Ptr ThreadPool -> IO ThreadPool
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ThreadPool -> ThreadPool
ThreadPool)
    wrappedPtrFree :: Maybe (GDestroyNotify ThreadPool)
wrappedPtrFree = GDestroyNotify ThreadPool -> Maybe (GDestroyNotify ThreadPool)
forall a. a -> Maybe a
Just GDestroyNotify ThreadPool
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ThreadPool`.
noThreadPool :: Maybe ThreadPool
noThreadPool :: Maybe ThreadPool
noThreadPool = Maybe ThreadPool
forall a. Maybe a
Nothing

-- | Get the value of the “@func@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' threadPool #func
-- @
getThreadPoolFunc :: MonadIO m => ThreadPool -> m (Maybe GLib.Callbacks.Func_WithClosures)
getThreadPoolFunc :: ThreadPool -> m (Maybe Func_WithClosures)
getThreadPoolFunc s :: ThreadPool
s = IO (Maybe Func_WithClosures) -> m (Maybe Func_WithClosures)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Func_WithClosures) -> m (Maybe Func_WithClosures))
-> IO (Maybe Func_WithClosures) -> m (Maybe Func_WithClosures)
forall a b. (a -> b) -> a -> b
$ ThreadPool
-> (Ptr ThreadPool -> IO (Maybe Func_WithClosures))
-> IO (Maybe Func_WithClosures)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ThreadPool
s ((Ptr ThreadPool -> IO (Maybe Func_WithClosures))
 -> IO (Maybe Func_WithClosures))
-> (Ptr ThreadPool -> IO (Maybe Func_WithClosures))
-> IO (Maybe Func_WithClosures)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ThreadPool
ptr -> do
    FunPtr Func_WithClosures
val <- Ptr (FunPtr Func_WithClosures) -> IO (FunPtr Func_WithClosures)
forall a. Storable a => Ptr a -> IO a
peek (Ptr ThreadPool
ptr Ptr ThreadPool -> Int -> Ptr (FunPtr Func_WithClosures)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (FunPtr GLib.Callbacks.C_Func)
    Maybe Func_WithClosures
result <- FunPtr Func_WithClosures
-> (FunPtr Func_WithClosures -> IO Func_WithClosures)
-> IO (Maybe Func_WithClosures)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr Func_WithClosures
val ((FunPtr Func_WithClosures -> IO Func_WithClosures)
 -> IO (Maybe Func_WithClosures))
-> (FunPtr Func_WithClosures -> IO Func_WithClosures)
-> IO (Maybe Func_WithClosures)
forall a b. (a -> b) -> a -> b
$ \val' :: FunPtr Func_WithClosures
val' -> do
        let val'' :: Func_WithClosures
val'' = FunPtr Func_WithClosures -> Func_WithClosures
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr Func_WithClosures -> Ptr () -> Ptr () -> m ()
GLib.Callbacks.dynamic_Func FunPtr Func_WithClosures
val'
        Func_WithClosures -> IO Func_WithClosures
forall (m :: * -> *) a. Monad m => a -> m a
return Func_WithClosures
val''
    Maybe Func_WithClosures -> IO (Maybe Func_WithClosures)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Func_WithClosures
result

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

-- | Set the value of the “@func@” 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' #func
-- @
clearThreadPoolFunc :: MonadIO m => ThreadPool -> m ()
clearThreadPoolFunc :: ThreadPool -> m ()
clearThreadPoolFunc s :: ThreadPool
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ThreadPool -> (Ptr ThreadPool -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ThreadPool
s ((Ptr ThreadPool -> IO ()) -> IO ())
-> (Ptr ThreadPool -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ThreadPool
ptr -> do
    Ptr (FunPtr Func_WithClosures) -> FunPtr Func_WithClosures -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ThreadPool
ptr Ptr ThreadPool -> Int -> Ptr (FunPtr Func_WithClosures)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (FunPtr Func_WithClosures
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GLib.Callbacks.C_Func)

#if defined(ENABLE_OVERLOADING)
data ThreadPoolFuncFieldInfo
instance AttrInfo ThreadPoolFuncFieldInfo where
    type AttrBaseTypeConstraint ThreadPoolFuncFieldInfo = (~) ThreadPool
    type AttrAllowedOps ThreadPoolFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ThreadPoolFuncFieldInfo = (~) (FunPtr GLib.Callbacks.C_Func)
    type AttrTransferTypeConstraint ThreadPoolFuncFieldInfo = (~)GLib.Callbacks.Func_WithClosures
    type AttrTransferType ThreadPoolFuncFieldInfo = (FunPtr GLib.Callbacks.C_Func)
    type AttrGetType ThreadPoolFuncFieldInfo = Maybe GLib.Callbacks.Func_WithClosures
    type AttrLabel ThreadPoolFuncFieldInfo = "func"
    type AttrOrigin ThreadPoolFuncFieldInfo = ThreadPool
    attrGet = getThreadPoolFunc
    attrSet = setThreadPoolFunc
    attrConstruct = undefined
    attrClear = clearThreadPoolFunc
    attrTransfer _ v = do
        GLib.Callbacks.mk_Func (GLib.Callbacks.wrap_Func Nothing v)

threadPool_func :: AttrLabelProxy "func"
threadPool_func = AttrLabelProxy

#endif


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

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

-- | Set the value of the “@user_data@” 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' #userData
-- @
clearThreadPoolUserData :: MonadIO m => ThreadPool -> m ()
clearThreadPoolUserData :: ThreadPool -> m ()
clearThreadPoolUserData s :: ThreadPool
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ThreadPool -> (Ptr ThreadPool -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ThreadPool
s ((Ptr ThreadPool -> IO ()) -> IO ())
-> (Ptr ThreadPool -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ThreadPool
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ThreadPool
ptr Ptr ThreadPool -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())

#if defined(ENABLE_OVERLOADING)
data ThreadPoolUserDataFieldInfo
instance AttrInfo ThreadPoolUserDataFieldInfo where
    type AttrBaseTypeConstraint ThreadPoolUserDataFieldInfo = (~) ThreadPool
    type AttrAllowedOps ThreadPoolUserDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ThreadPoolUserDataFieldInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint ThreadPoolUserDataFieldInfo = (~)(Ptr ())
    type AttrTransferType ThreadPoolUserDataFieldInfo = (Ptr ())
    type AttrGetType ThreadPoolUserDataFieldInfo = Ptr ()
    type AttrLabel ThreadPoolUserDataFieldInfo = "user_data"
    type AttrOrigin ThreadPoolUserDataFieldInfo = ThreadPool
    attrGet = getThreadPoolUserData
    attrSet = setThreadPoolUserData
    attrConstruct = undefined
    attrClear = clearThreadPoolUserData
    attrTransfer _ v = do
        return v

threadPool_userData :: AttrLabelProxy "userData"
threadPool_userData = AttrLabelProxy

#endif


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

-- | Set the value of the “@exclusive@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' threadPool [ #exclusive 'Data.GI.Base.Attributes.:=' value ]
-- @
setThreadPoolExclusive :: MonadIO m => ThreadPool -> Bool -> m ()
setThreadPoolExclusive :: ThreadPool -> Bool -> m ()
setThreadPoolExclusive s :: ThreadPool
s val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ThreadPool -> (Ptr ThreadPool -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ThreadPool
s ((Ptr ThreadPool -> IO ()) -> IO ())
-> (Ptr ThreadPool -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ThreadPool
ptr -> do
    let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
val
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ThreadPool
ptr Ptr ThreadPool -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (CInt
val' :: CInt)

#if defined(ENABLE_OVERLOADING)
data ThreadPoolExclusiveFieldInfo
instance AttrInfo ThreadPoolExclusiveFieldInfo where
    type AttrBaseTypeConstraint ThreadPoolExclusiveFieldInfo = (~) ThreadPool
    type AttrAllowedOps ThreadPoolExclusiveFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ThreadPoolExclusiveFieldInfo = (~) Bool
    type AttrTransferTypeConstraint ThreadPoolExclusiveFieldInfo = (~)Bool
    type AttrTransferType ThreadPoolExclusiveFieldInfo = Bool
    type AttrGetType ThreadPoolExclusiveFieldInfo = Bool
    type AttrLabel ThreadPoolExclusiveFieldInfo = "exclusive"
    type AttrOrigin ThreadPoolExclusiveFieldInfo = ThreadPool
    attrGet = getThreadPoolExclusive
    attrSet = setThreadPoolExclusive
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

threadPool_exclusive :: AttrLabelProxy "exclusive"
threadPool_exclusive = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ThreadPool
type instance O.AttributeList ThreadPool = ThreadPoolAttributeList
type ThreadPoolAttributeList = ('[ '("func", ThreadPoolFuncFieldInfo), '("userData", ThreadPoolUserDataFieldInfo), '("exclusive", ThreadPoolExclusiveFieldInfo)] :: [(Symbol, *)])
#endif

-- method ThreadPool::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pool"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ThreadPool" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThreadPool" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "immediate"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "should @pool shut down immediately?"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "wait_"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "should the function wait for all tasks to be finished?"
--                 , 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_pool_free" g_thread_pool_free :: 
    Ptr ThreadPool ->                       -- pool : TInterface (Name {namespace = "GLib", name = "ThreadPool"})
    CInt ->                                 -- immediate : TBasicType TBoolean
    CInt ->                                 -- wait_ : TBasicType TBoolean
    IO ()

-- | Frees all resources allocated for /@pool@/.
-- 
-- If /@immediate@/ is 'P.True', no new task is processed for /@pool@/.
-- Otherwise /@pool@/ is not freed before the last task is processed.
-- Note however, that no thread of this pool is interrupted while
-- processing a task. Instead at least all still running threads
-- can finish their tasks before the /@pool@/ is freed.
-- 
-- If /@wait_@/ is 'P.True', the functions does not return before all
-- tasks to be processed (dependent on /@immediate@/, whether all
-- or only the currently running) are ready.
-- Otherwise the function returns immediately.
-- 
-- After calling this function /@pool@/ must not be used anymore.
threadPoolFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ThreadPool
    -- ^ /@pool@/: a t'GI.GLib.Structs.ThreadPool.ThreadPool'
    -> Bool
    -- ^ /@immediate@/: should /@pool@/ shut down immediately?
    -> Bool
    -- ^ /@wait_@/: should the function wait for all tasks to be finished?
    -> m ()
threadPoolFree :: ThreadPool -> Bool -> Bool -> m ()
threadPoolFree pool :: ThreadPool
pool immediate :: Bool
immediate wait_ :: Bool
wait_ = 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 ThreadPool
pool' <- ThreadPool -> IO (Ptr ThreadPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ThreadPool
pool
    let immediate' :: CInt
immediate' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
immediate
    let wait_' :: CInt
wait_' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
wait_
    Ptr ThreadPool -> CInt -> CInt -> IO ()
g_thread_pool_free Ptr ThreadPool
pool' CInt
immediate' CInt
wait_'
    ThreadPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ThreadPool
pool
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ThreadPoolFreeMethodInfo
instance (signature ~ (Bool -> Bool -> m ()), MonadIO m) => O.MethodInfo ThreadPoolFreeMethodInfo ThreadPool signature where
    overloadedMethod = threadPoolFree

#endif

-- method ThreadPool::get_max_threads
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pool"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ThreadPool" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThreadPool" , 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_thread_pool_get_max_threads" g_thread_pool_get_max_threads :: 
    Ptr ThreadPool ->                       -- pool : TInterface (Name {namespace = "GLib", name = "ThreadPool"})
    IO Int32

-- | Returns the maximal number of threads for /@pool@/.
threadPoolGetMaxThreads ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ThreadPool
    -- ^ /@pool@/: a t'GI.GLib.Structs.ThreadPool.ThreadPool'
    -> m Int32
    -- ^ __Returns:__ the maximal number of threads
threadPoolGetMaxThreads :: ThreadPool -> m Int32
threadPoolGetMaxThreads pool :: ThreadPool
pool = 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 ThreadPool
pool' <- ThreadPool -> IO (Ptr ThreadPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ThreadPool
pool
    Int32
result <- Ptr ThreadPool -> IO Int32
g_thread_pool_get_max_threads Ptr ThreadPool
pool'
    ThreadPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ThreadPool
pool
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ThreadPoolGetMaxThreadsMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo ThreadPoolGetMaxThreadsMethodInfo ThreadPool signature where
    overloadedMethod = threadPoolGetMaxThreads

#endif

-- method ThreadPool::get_num_threads
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pool"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ThreadPool" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThreadPool" , 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_thread_pool_get_num_threads" g_thread_pool_get_num_threads :: 
    Ptr ThreadPool ->                       -- pool : TInterface (Name {namespace = "GLib", name = "ThreadPool"})
    IO Word32

-- | Returns the number of threads currently running in /@pool@/.
threadPoolGetNumThreads ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ThreadPool
    -- ^ /@pool@/: a t'GI.GLib.Structs.ThreadPool.ThreadPool'
    -> m Word32
    -- ^ __Returns:__ the number of threads currently running
threadPoolGetNumThreads :: ThreadPool -> m Word32
threadPoolGetNumThreads pool :: ThreadPool
pool = 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 ThreadPool
pool' <- ThreadPool -> IO (Ptr ThreadPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ThreadPool
pool
    Word32
result <- Ptr ThreadPool -> IO Word32
g_thread_pool_get_num_threads Ptr ThreadPool
pool'
    ThreadPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ThreadPool
pool
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data ThreadPoolGetNumThreadsMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ThreadPoolGetNumThreadsMethodInfo ThreadPool signature where
    overloadedMethod = threadPoolGetNumThreads

#endif

-- method ThreadPool::move_to_front
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pool"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ThreadPool" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThreadPool" , 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 "an unprocessed item in the pool"
--                 , 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_thread_pool_move_to_front" g_thread_pool_move_to_front :: 
    Ptr ThreadPool ->                       -- pool : TInterface (Name {namespace = "GLib", name = "ThreadPool"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO CInt

-- | Moves the item to the front of the queue of unprocessed
-- items, so that it will be processed next.
-- 
-- /Since: 2.46/
threadPoolMoveToFront ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ThreadPool
    -- ^ /@pool@/: a t'GI.GLib.Structs.ThreadPool.ThreadPool'
    -> Ptr ()
    -- ^ /@data@/: an unprocessed item in the pool
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the item was found and moved
threadPoolMoveToFront :: ThreadPool -> Ptr () -> m Bool
threadPoolMoveToFront pool :: ThreadPool
pool 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 ThreadPool
pool' <- ThreadPool -> IO (Ptr ThreadPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ThreadPool
pool
    CInt
result <- Ptr ThreadPool -> Ptr () -> IO CInt
g_thread_pool_move_to_front Ptr ThreadPool
pool' Ptr ()
data_
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    ThreadPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ThreadPool
pool
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ThreadPoolMoveToFrontMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.MethodInfo ThreadPoolMoveToFrontMethodInfo ThreadPool signature where
    overloadedMethod = threadPoolMoveToFront

#endif

-- method ThreadPool::push
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pool"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ThreadPool" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThreadPool" , 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 "a new task for @pool"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_thread_pool_push" g_thread_pool_push :: 
    Ptr ThreadPool ->                       -- pool : TInterface (Name {namespace = "GLib", name = "ThreadPool"})
    Ptr () ->                               -- data : TBasicType TPtr
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Inserts /@data@/ into the list of tasks to be executed by /@pool@/.
-- 
-- When the number of currently running threads is lower than the
-- maximal allowed number of threads, a new thread is started (or
-- reused) with the properties given to @/g_thread_pool_new()/@.
-- Otherwise, /@data@/ stays in the queue until a thread in this pool
-- finishes its previous task and processes /@data@/.
-- 
-- /@error@/ can be 'P.Nothing' to ignore errors, or non-'P.Nothing' to report
-- errors. An error can only occur when a new thread couldn\'t be
-- created. In that case /@data@/ is simply appended to the queue of
-- work to do.
-- 
-- Before version 2.32, this function did not return a success status.
threadPoolPush ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ThreadPool
    -- ^ /@pool@/: a t'GI.GLib.Structs.ThreadPool.ThreadPool'
    -> Ptr ()
    -- ^ /@data@/: a new task for /@pool@/
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
threadPoolPush :: ThreadPool -> Ptr () -> m ()
threadPoolPush pool :: ThreadPool
pool 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 ThreadPool
pool' <- ThreadPool -> IO (Ptr ThreadPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ThreadPool
pool
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr ThreadPool -> Ptr () -> Ptr (Ptr GError) -> IO CInt
g_thread_pool_push Ptr ThreadPool
pool' Ptr ()
data_
        ThreadPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ThreadPool
pool
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data ThreadPoolPushMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo ThreadPoolPushMethodInfo ThreadPool signature where
    overloadedMethod = threadPoolPush

#endif

-- method ThreadPool::set_max_threads
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pool"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ThreadPool" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThreadPool" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max_threads"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a new maximal number of threads for @pool,\n    or -1 for unlimited"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_thread_pool_set_max_threads" g_thread_pool_set_max_threads :: 
    Ptr ThreadPool ->                       -- pool : TInterface (Name {namespace = "GLib", name = "ThreadPool"})
    Int32 ->                                -- max_threads : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Sets the maximal allowed number of threads for /@pool@/.
-- A value of -1 means that the maximal number of threads
-- is unlimited. If /@pool@/ is an exclusive thread pool, setting
-- the maximal number of threads to -1 is not allowed.
-- 
-- Setting /@maxThreads@/ to 0 means stopping all work for /@pool@/.
-- It is effectively frozen until /@maxThreads@/ is set to a non-zero
-- value again.
-- 
-- A thread is never terminated while calling /@func@/, as supplied by
-- @/g_thread_pool_new()/@. Instead the maximal number of threads only
-- has effect for the allocation of new threads in 'GI.GLib.Structs.ThreadPool.threadPoolPush'.
-- A new thread is allocated, whenever the number of currently
-- running threads in /@pool@/ is smaller than the maximal number.
-- 
-- /@error@/ can be 'P.Nothing' to ignore errors, or non-'P.Nothing' to report
-- errors. An error can only occur when a new thread couldn\'t be
-- created.
-- 
-- Before version 2.32, this function did not return a success status.
threadPoolSetMaxThreads ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ThreadPool
    -- ^ /@pool@/: a t'GI.GLib.Structs.ThreadPool.ThreadPool'
    -> Int32
    -- ^ /@maxThreads@/: a new maximal number of threads for /@pool@/,
    --     or -1 for unlimited
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
threadPoolSetMaxThreads :: ThreadPool -> Int32 -> m ()
threadPoolSetMaxThreads pool :: ThreadPool
pool maxThreads :: Int32
maxThreads = 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 ThreadPool
pool' <- ThreadPool -> IO (Ptr ThreadPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ThreadPool
pool
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr ThreadPool -> Int32 -> Ptr (Ptr GError) -> IO CInt
g_thread_pool_set_max_threads Ptr ThreadPool
pool' Int32
maxThreads
        ThreadPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ThreadPool
pool
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data ThreadPoolSetMaxThreadsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.MethodInfo ThreadPoolSetMaxThreadsMethodInfo ThreadPool signature where
    overloadedMethod = threadPoolSetMaxThreads

#endif

-- method ThreadPool::unprocessed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pool"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ThreadPool" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThreadPool" , 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_thread_pool_unprocessed" g_thread_pool_unprocessed :: 
    Ptr ThreadPool ->                       -- pool : TInterface (Name {namespace = "GLib", name = "ThreadPool"})
    IO Word32

-- | Returns the number of tasks still unprocessed in /@pool@/.
threadPoolUnprocessed ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ThreadPool
    -- ^ /@pool@/: a t'GI.GLib.Structs.ThreadPool.ThreadPool'
    -> m Word32
    -- ^ __Returns:__ the number of unprocessed tasks
threadPoolUnprocessed :: ThreadPool -> m Word32
threadPoolUnprocessed pool :: ThreadPool
pool = 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 ThreadPool
pool' <- ThreadPool -> IO (Ptr ThreadPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ThreadPool
pool
    Word32
result <- Ptr ThreadPool -> IO Word32
g_thread_pool_unprocessed Ptr ThreadPool
pool'
    ThreadPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ThreadPool
pool
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data ThreadPoolUnprocessedMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ThreadPoolUnprocessedMethodInfo ThreadPool signature where
    overloadedMethod = threadPoolUnprocessed

#endif

-- method ThreadPool::get_max_idle_time
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_get_max_idle_time" g_thread_pool_get_max_idle_time :: 
    IO Word32

-- | This function will return the maximum /@interval@/ that a
-- thread will wait in the thread pool for new tasks before
-- being stopped.
-- 
-- If this function returns 0, threads waiting in the thread
-- pool for new work are not stopped.
-- 
-- /Since: 2.10/
threadPoolGetMaxIdleTime ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Word32
    -- ^ __Returns:__ the maximum /@interval@/ (milliseconds) to wait
    --     for new tasks in the thread pool before stopping the
    --     thread
threadPoolGetMaxIdleTime :: m Word32
threadPoolGetMaxIdleTime  = 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_pool_get_max_idle_time
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThreadPool::get_max_unused_threads
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_get_max_unused_threads" g_thread_pool_get_max_unused_threads :: 
    IO Int32

-- | Returns the maximal allowed number of unused threads.
threadPoolGetMaxUnusedThreads ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Int32
    -- ^ __Returns:__ the maximal number of unused threads
threadPoolGetMaxUnusedThreads :: m Int32
threadPoolGetMaxUnusedThreads  = 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
    Int32
result <- IO Int32
g_thread_pool_get_max_unused_threads
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThreadPool::get_num_unused_threads
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_get_num_unused_threads" g_thread_pool_get_num_unused_threads :: 
    IO Word32

-- | Returns the number of currently unused threads.
threadPoolGetNumUnusedThreads ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Word32
    -- ^ __Returns:__ the number of currently unused threads
threadPoolGetNumUnusedThreads :: m Word32
threadPoolGetNumUnusedThreads  = 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_pool_get_num_unused_threads
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThreadPool::set_max_idle_time
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "interval"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the maximum @interval (in milliseconds)\n    a thread can be idle"
--                 , 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_pool_set_max_idle_time" g_thread_pool_set_max_idle_time :: 
    Word32 ->                               -- interval : TBasicType TUInt
    IO ()

-- | This function will set the maximum /@interval@/ that a thread
-- waiting in the pool for new tasks can be idle for before
-- being stopped. This function is similar to calling
-- 'GI.GLib.Functions.threadPoolStopUnusedThreads' on a regular timeout,
-- except this is done on a per thread basis.
-- 
-- By setting /@interval@/ to 0, idle threads will not be stopped.
-- 
-- The default value is 15000 (15 seconds).
-- 
-- /Since: 2.10/
threadPoolSetMaxIdleTime ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word32
    -- ^ /@interval@/: the maximum /@interval@/ (in milliseconds)
    --     a thread can be idle
    -> m ()
threadPoolSetMaxIdleTime :: Word32 -> m ()
threadPoolSetMaxIdleTime interval :: Word32
interval = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Word32 -> IO ()
g_thread_pool_set_max_idle_time Word32
interval
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThreadPool::set_max_unused_threads
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "max_threads"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "maximal number of unused threads"
--                 , 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_pool_set_max_unused_threads" g_thread_pool_set_max_unused_threads :: 
    Int32 ->                                -- max_threads : TBasicType TInt
    IO ()

-- | Sets the maximal number of unused threads to /@maxThreads@/.
-- If /@maxThreads@/ is -1, no limit is imposed on the number
-- of unused threads.
-- 
-- The default value is 2.
threadPoolSetMaxUnusedThreads ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@maxThreads@/: maximal number of unused threads
    -> m ()
threadPoolSetMaxUnusedThreads :: Int32 -> m ()
threadPoolSetMaxUnusedThreads maxThreads :: Int32
maxThreads = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Int32 -> IO ()
g_thread_pool_set_max_unused_threads Int32
maxThreads
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThreadPool::stop_unused_threads
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Stops all currently unused threads. This does not change the
-- maximal number of unused threads. This function can be used to
-- regularly stop all unused threads e.g. from @/g_timeout_add()/@.
threadPoolStopUnusedThreads ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ()
threadPoolStopUnusedThreads :: m ()
threadPoolStopUnusedThreads  = 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_pool_stop_unused_threads
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveThreadPoolMethod (t :: Symbol) (o :: *) :: * where
    ResolveThreadPoolMethod "free" o = ThreadPoolFreeMethodInfo
    ResolveThreadPoolMethod "moveToFront" o = ThreadPoolMoveToFrontMethodInfo
    ResolveThreadPoolMethod "push" o = ThreadPoolPushMethodInfo
    ResolveThreadPoolMethod "unprocessed" o = ThreadPoolUnprocessedMethodInfo
    ResolveThreadPoolMethod "getMaxThreads" o = ThreadPoolGetMaxThreadsMethodInfo
    ResolveThreadPoolMethod "getNumThreads" o = ThreadPoolGetNumThreadsMethodInfo
    ResolveThreadPoolMethod "setMaxThreads" o = ThreadPoolSetMaxThreadsMethodInfo
    ResolveThreadPoolMethod l o = O.MethodResolutionFailed l o

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

#endif