module Ki.Internal.ThreadOptions
( ThreadOptions (..),
defaultThreadOptions,
)
where
import Control.Exception (MaskingState (..))
import Ki.Internal.ByteCount (ByteCount)
import Ki.Internal.ThreadAffinity (ThreadAffinity (..))
data ThreadOptions = ThreadOptions
{ ThreadOptions -> ThreadAffinity
affinity :: ThreadAffinity,
ThreadOptions -> Maybe ByteCount
allocationLimit :: Maybe ByteCount,
ThreadOptions -> String
label :: String,
ThreadOptions -> MaskingState
maskingState :: MaskingState
}
deriving stock (ThreadOptions -> ThreadOptions -> Bool
(ThreadOptions -> ThreadOptions -> Bool)
-> (ThreadOptions -> ThreadOptions -> Bool) -> Eq ThreadOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadOptions -> ThreadOptions -> Bool
== :: ThreadOptions -> ThreadOptions -> Bool
$c/= :: ThreadOptions -> ThreadOptions -> Bool
/= :: ThreadOptions -> ThreadOptions -> Bool
Eq, Int -> ThreadOptions -> ShowS
[ThreadOptions] -> ShowS
ThreadOptions -> String
(Int -> ThreadOptions -> ShowS)
-> (ThreadOptions -> String)
-> ([ThreadOptions] -> ShowS)
-> Show ThreadOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ThreadOptions -> ShowS
showsPrec :: Int -> ThreadOptions -> ShowS
$cshow :: ThreadOptions -> String
show :: ThreadOptions -> String
$cshowList :: [ThreadOptions] -> ShowS
showList :: [ThreadOptions] -> ShowS
Show)
defaultThreadOptions :: ThreadOptions
defaultThreadOptions :: ThreadOptions
defaultThreadOptions =
ThreadOptions
{ $sel:affinity:ThreadOptions :: ThreadAffinity
affinity = ThreadAffinity
Unbound,
$sel:allocationLimit:ThreadOptions :: Maybe ByteCount
allocationLimit = Maybe ByteCount
forall a. Maybe a
Nothing,
$sel:label:ThreadOptions :: String
label = String
"",
$sel:maskingState:ThreadOptions :: MaskingState
maskingState = MaskingState
Unmasked
}