{-# LANGUAGE CPP #-}
module Colog.Concurrent.Internal
( BackgroundWorker (..)
, Capacity (..)
, mkCapacity
) where
import Control.Concurrent (ThreadId)
import Control.Concurrent.STM (STM, TVar)
import Numeric.Natural (Natural)
#if MIN_VERSION_stm(2,5,0)
data Capacity = Capacity Natural (Maybe Natural)
deriving stock Int -> Capacity -> ShowS
[Capacity] -> ShowS
Capacity -> String
(Int -> Capacity -> ShowS)
-> (Capacity -> String) -> ([Capacity] -> ShowS) -> Show Capacity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Capacity] -> ShowS
$cshowList :: [Capacity] -> ShowS
show :: Capacity -> String
$cshow :: Capacity -> String
showsPrec :: Int -> Capacity -> ShowS
$cshowsPrec :: Int -> Capacity -> ShowS
Show
#else
data Capacity = Capacity Int (Maybe Natural)
deriving stock Show
#endif
mkCapacity
:: Natural
-> Maybe Natural
-> Capacity
mkCapacity :: Natural -> Maybe Natural -> Capacity
mkCapacity Natural
n = Natural -> Maybe Natural -> Capacity
Capacity (Natural -> Natural
forall a. a -> a
mk Natural
n) where
#if MIN_VERSION_stm(2,5,0)
mk :: a -> a
mk = a -> a
forall a. a -> a
id
#else
mk = fromIntegral
#endif
data BackgroundWorker msg = BackgroundWorker
{ BackgroundWorker msg -> ThreadId
backgroundWorkerThreadId :: !ThreadId
, BackgroundWorker msg -> msg -> STM ()
backgroundWorkerWrite :: msg -> STM ()
, BackgroundWorker msg -> TVar Bool
backgroundWorkerIsAlive :: TVar Bool
}