module GI.GLib.Structs.ThreadPool
(
ThreadPool(..) ,
newZeroThreadPool ,
noThreadPool ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
ThreadPoolFreeMethodInfo ,
#endif
threadPoolFree ,
threadPoolGetMaxIdleTime ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
ThreadPoolGetMaxThreadsMethodInfo ,
#endif
threadPoolGetMaxThreads ,
threadPoolGetMaxUnusedThreads ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
ThreadPoolGetNumThreadsMethodInfo ,
#endif
threadPoolGetNumThreads ,
threadPoolGetNumUnusedThreads ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
ThreadPoolMoveToFrontMethodInfo ,
#endif
threadPoolMoveToFront ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
ThreadPoolPushMethodInfo ,
#endif
threadPoolPush ,
threadPoolSetMaxIdleTime ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
ThreadPoolSetMaxThreadsMethodInfo ,
#endif
threadPoolSetMaxThreads ,
threadPoolSetMaxUnusedThreads ,
threadPoolStopUnusedThreads ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
ThreadPoolUnprocessedMethodInfo ,
#endif
threadPoolUnprocessed ,
getThreadPoolExclusive ,
setThreadPoolExclusive ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
threadPool_exclusive ,
#endif
clearThreadPoolFunc ,
getThreadPoolFunc ,
setThreadPoolFunc ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
threadPool_func ,
#endif
clearThreadPoolUserData ,
getThreadPoolUserData ,
setThreadPoolUserData ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
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.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 GI.GLib.Callbacks as GLib.Callbacks
newtype ThreadPool = ThreadPool (ManagedPtr ThreadPool)
instance WrappedPtr ThreadPool where
wrappedPtrCalloc = callocBytes 24
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 24 >=> wrapPtr ThreadPool)
wrappedPtrFree = Just ptr_to_g_free
newZeroThreadPool :: MonadIO m => m ThreadPool
newZeroThreadPool = liftIO $ wrappedPtrCalloc >>= wrapPtr ThreadPool
instance tag ~ 'AttrSet => Constructible ThreadPool tag where
new _ attrs = do
o <- newZeroThreadPool
GI.Attributes.set o attrs
return o
noThreadPool :: Maybe ThreadPool
noThreadPool = Nothing
getThreadPoolFunc :: MonadIO m => ThreadPool -> m (Maybe GLib.Callbacks.Func_WithClosures)
getThreadPoolFunc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO (FunPtr GLib.Callbacks.C_Func)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_Func val'
return val''
return result
setThreadPoolFunc :: MonadIO m => ThreadPool -> FunPtr GLib.Callbacks.C_Func -> m ()
setThreadPoolFunc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (val :: FunPtr GLib.Callbacks.C_Func)
clearThreadPoolFunc :: MonadIO m => ThreadPool -> m ()
clearThreadPoolFunc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_Func)
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolFuncFieldInfo
instance AttrInfo ThreadPoolFuncFieldInfo where
type AttrAllowedOps ThreadPoolFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint ThreadPoolFuncFieldInfo = (~) (FunPtr GLib.Callbacks.C_Func)
type AttrBaseTypeConstraint ThreadPoolFuncFieldInfo = (~) ThreadPool
type AttrGetType ThreadPoolFuncFieldInfo = Maybe GLib.Callbacks.Func_WithClosures
type AttrLabel ThreadPoolFuncFieldInfo = "func"
type AttrOrigin ThreadPoolFuncFieldInfo = ThreadPool
attrGet _ = getThreadPoolFunc
attrSet _ = setThreadPoolFunc
attrConstruct = undefined
attrClear _ = clearThreadPoolFunc
threadPool_func :: AttrLabelProxy "func"
threadPool_func = AttrLabelProxy
#endif
getThreadPoolUserData :: MonadIO m => ThreadPool -> m (Ptr ())
getThreadPoolUserData s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO (Ptr ())
return val
setThreadPoolUserData :: MonadIO m => ThreadPool -> Ptr () -> m ()
setThreadPoolUserData s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr ())
clearThreadPoolUserData :: MonadIO m => ThreadPool -> m ()
clearThreadPoolUserData s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr ())
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolUserDataFieldInfo
instance AttrInfo ThreadPoolUserDataFieldInfo where
type AttrAllowedOps ThreadPoolUserDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint ThreadPoolUserDataFieldInfo = (~) (Ptr ())
type AttrBaseTypeConstraint ThreadPoolUserDataFieldInfo = (~) ThreadPool
type AttrGetType ThreadPoolUserDataFieldInfo = Ptr ()
type AttrLabel ThreadPoolUserDataFieldInfo = "user_data"
type AttrOrigin ThreadPoolUserDataFieldInfo = ThreadPool
attrGet _ = getThreadPoolUserData
attrSet _ = setThreadPoolUserData
attrConstruct = undefined
attrClear _ = clearThreadPoolUserData
threadPool_userData :: AttrLabelProxy "userData"
threadPool_userData = AttrLabelProxy
#endif
getThreadPoolExclusive :: MonadIO m => ThreadPool -> m Bool
getThreadPoolExclusive s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO CInt
let val' = (/= 0) val
return val'
setThreadPoolExclusive :: MonadIO m => ThreadPool -> Bool -> m ()
setThreadPoolExclusive s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 16) (val' :: CInt)
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolExclusiveFieldInfo
instance AttrInfo ThreadPoolExclusiveFieldInfo where
type AttrAllowedOps ThreadPoolExclusiveFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint ThreadPoolExclusiveFieldInfo = (~) Bool
type AttrBaseTypeConstraint ThreadPoolExclusiveFieldInfo = (~) ThreadPool
type AttrGetType ThreadPoolExclusiveFieldInfo = Bool
type AttrLabel ThreadPoolExclusiveFieldInfo = "exclusive"
type AttrOrigin ThreadPoolExclusiveFieldInfo = ThreadPool
attrGet _ = getThreadPoolExclusive
attrSet _ = setThreadPoolExclusive
attrConstruct = undefined
attrClear _ = undefined
threadPool_exclusive :: AttrLabelProxy "exclusive"
threadPool_exclusive = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList ThreadPool
type instance O.AttributeList ThreadPool = ThreadPoolAttributeList
type ThreadPoolAttributeList = ('[ '("func", ThreadPoolFuncFieldInfo), '("userData", ThreadPoolUserDataFieldInfo), '("exclusive", ThreadPoolExclusiveFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_thread_pool_free" g_thread_pool_free ::
Ptr ThreadPool ->
CInt ->
CInt ->
IO ()
threadPoolFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
ThreadPool
-> Bool
-> Bool
-> m ()
threadPoolFree pool immediate wait_ = liftIO $ do
pool' <- unsafeManagedPtrGetPtr pool
let immediate' = (fromIntegral . fromEnum) immediate
let wait_' = (fromIntegral . fromEnum) wait_
g_thread_pool_free pool' immediate' wait_'
touchManagedPtr pool
return ()
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolFreeMethodInfo
instance (signature ~ (Bool -> Bool -> m ()), MonadIO m) => O.MethodInfo ThreadPoolFreeMethodInfo ThreadPool signature where
overloadedMethod _ = threadPoolFree
#endif
foreign import ccall "g_thread_pool_get_max_threads" g_thread_pool_get_max_threads ::
Ptr ThreadPool ->
IO Int32
threadPoolGetMaxThreads ::
(B.CallStack.HasCallStack, MonadIO m) =>
ThreadPool
-> m Int32
threadPoolGetMaxThreads pool = liftIO $ do
pool' <- unsafeManagedPtrGetPtr pool
result <- g_thread_pool_get_max_threads pool'
touchManagedPtr pool
return result
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolGetMaxThreadsMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo ThreadPoolGetMaxThreadsMethodInfo ThreadPool signature where
overloadedMethod _ = threadPoolGetMaxThreads
#endif
foreign import ccall "g_thread_pool_get_num_threads" g_thread_pool_get_num_threads ::
Ptr ThreadPool ->
IO Word32
threadPoolGetNumThreads ::
(B.CallStack.HasCallStack, MonadIO m) =>
ThreadPool
-> m Word32
threadPoolGetNumThreads pool = liftIO $ do
pool' <- unsafeManagedPtrGetPtr pool
result <- g_thread_pool_get_num_threads pool'
touchManagedPtr pool
return result
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolGetNumThreadsMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ThreadPoolGetNumThreadsMethodInfo ThreadPool signature where
overloadedMethod _ = threadPoolGetNumThreads
#endif
foreign import ccall "g_thread_pool_move_to_front" g_thread_pool_move_to_front ::
Ptr ThreadPool ->
Ptr () ->
IO CInt
threadPoolMoveToFront ::
(B.CallStack.HasCallStack, MonadIO m) =>
ThreadPool
-> Ptr ()
-> m Bool
threadPoolMoveToFront pool data_ = liftIO $ do
pool' <- unsafeManagedPtrGetPtr pool
result <- g_thread_pool_move_to_front pool' data_
let result' = (/= 0) result
touchManagedPtr pool
return result'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolMoveToFrontMethodInfo
instance (signature ~ (Ptr () -> m Bool), MonadIO m) => O.MethodInfo ThreadPoolMoveToFrontMethodInfo ThreadPool signature where
overloadedMethod _ = threadPoolMoveToFront
#endif
foreign import ccall "g_thread_pool_push" g_thread_pool_push ::
Ptr ThreadPool ->
Ptr () ->
Ptr (Ptr GError) ->
IO CInt
threadPoolPush ::
(B.CallStack.HasCallStack, MonadIO m) =>
ThreadPool
-> Ptr ()
-> m ()
threadPoolPush pool data_ = liftIO $ do
pool' <- unsafeManagedPtrGetPtr pool
onException (do
_ <- propagateGError $ g_thread_pool_push pool' data_
touchManagedPtr pool
return ()
) (do
return ()
)
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolPushMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.MethodInfo ThreadPoolPushMethodInfo ThreadPool signature where
overloadedMethod _ = threadPoolPush
#endif
foreign import ccall "g_thread_pool_set_max_threads" g_thread_pool_set_max_threads ::
Ptr ThreadPool ->
Int32 ->
Ptr (Ptr GError) ->
IO CInt
threadPoolSetMaxThreads ::
(B.CallStack.HasCallStack, MonadIO m) =>
ThreadPool
-> Int32
-> m ()
threadPoolSetMaxThreads pool maxThreads = liftIO $ do
pool' <- unsafeManagedPtrGetPtr pool
onException (do
_ <- propagateGError $ g_thread_pool_set_max_threads pool' maxThreads
touchManagedPtr pool
return ()
) (do
return ()
)
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolSetMaxThreadsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.MethodInfo ThreadPoolSetMaxThreadsMethodInfo ThreadPool signature where
overloadedMethod _ = threadPoolSetMaxThreads
#endif
foreign import ccall "g_thread_pool_unprocessed" g_thread_pool_unprocessed ::
Ptr ThreadPool ->
IO Word32
threadPoolUnprocessed ::
(B.CallStack.HasCallStack, MonadIO m) =>
ThreadPool
-> m Word32
threadPoolUnprocessed pool = liftIO $ do
pool' <- unsafeManagedPtrGetPtr pool
result <- g_thread_pool_unprocessed pool'
touchManagedPtr pool
return result
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ThreadPoolUnprocessedMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ThreadPoolUnprocessedMethodInfo ThreadPool signature where
overloadedMethod _ = threadPoolUnprocessed
#endif
foreign import ccall "g_thread_pool_get_max_idle_time" g_thread_pool_get_max_idle_time ::
IO Word32
threadPoolGetMaxIdleTime ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Word32
threadPoolGetMaxIdleTime = liftIO $ do
result <- g_thread_pool_get_max_idle_time
return result
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif
foreign import ccall "g_thread_pool_get_max_unused_threads" g_thread_pool_get_max_unused_threads ::
IO Int32
threadPoolGetMaxUnusedThreads ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Int32
threadPoolGetMaxUnusedThreads = liftIO $ do
result <- g_thread_pool_get_max_unused_threads
return result
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif
foreign import ccall "g_thread_pool_get_num_unused_threads" g_thread_pool_get_num_unused_threads ::
IO Word32
threadPoolGetNumUnusedThreads ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Word32
threadPoolGetNumUnusedThreads = liftIO $ do
result <- g_thread_pool_get_num_unused_threads
return result
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif
foreign import ccall "g_thread_pool_set_max_idle_time" g_thread_pool_set_max_idle_time ::
Word32 ->
IO ()
threadPoolSetMaxIdleTime ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word32
-> m ()
threadPoolSetMaxIdleTime interval = liftIO $ do
g_thread_pool_set_max_idle_time interval
return ()
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif
foreign import ccall "g_thread_pool_set_max_unused_threads" g_thread_pool_set_max_unused_threads ::
Int32 ->
IO ()
threadPoolSetMaxUnusedThreads ::
(B.CallStack.HasCallStack, MonadIO m) =>
Int32
-> m ()
threadPoolSetMaxUnusedThreads maxThreads = liftIO $ do
g_thread_pool_set_max_unused_threads maxThreads
return ()
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif
foreign import ccall "g_thread_pool_stop_unused_threads" g_thread_pool_stop_unused_threads ::
IO ()
threadPoolStopUnusedThreads ::
(B.CallStack.HasCallStack, MonadIO m) =>
m ()
threadPoolStopUnusedThreads = liftIO $ do
g_thread_pool_stop_unused_threads
return ()
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
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) => O.IsLabelProxy t (ThreadPool -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveThreadPoolMethod t ThreadPool, O.MethodInfo info ThreadPool p) => O.IsLabel t (ThreadPool -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif
#endif