{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_HADDOCK hide, not-home #-}
{-# LANGUAGE Unsafe #-}
module Control.Scheduler.Internal
( Scheduler(..)
, WorkerStates(..)
, SchedulerWS(..)
, Jobs(..)
, Results(..)
, SchedulerOutcome(..)
, WorkerException(..)
, WorkerTerminateException(..)
, MutexException(..)
) where
import Control.Exception
import Control.Scheduler.Computation
import Control.Scheduler.Queue
import Data.IORef
import Data.Primitive.Array
data Results a
= Finished ![a]
| FinishedEarly ![a] !a
| FinishedEarlyWith !a
deriving (Show, Read, Eq)
instance Functor Results where
fmap f =
\case
Finished xs -> Finished (fmap f xs)
FinishedEarly xs x -> FinishedEarly (fmap f xs) (f x)
FinishedEarlyWith x -> FinishedEarlyWith (f x)
instance Foldable Results where
foldr f acc =
\case
Finished xs -> foldr f acc xs
FinishedEarly xs x -> foldr f (f x acc) xs
FinishedEarlyWith x -> f x acc
foldr1 f =
\case
Finished xs -> foldr1 f xs
FinishedEarly xs x -> foldr f x xs
FinishedEarlyWith x -> x
instance Traversable Results where
traverse f =
\case
Finished xs -> Finished <$> traverse f xs
FinishedEarly xs x -> FinishedEarly <$> traverse f xs <*> f x
FinishedEarlyWith x -> FinishedEarlyWith <$> f x
data Jobs m a = Jobs
{ jobsNumWorkers :: {-# UNPACK #-} !Int
, jobsQueue :: !(JQueue m a)
, jobsCountRef :: !(IORef Int)
}
data Scheduler m a = Scheduler
{ _numWorkers :: {-# UNPACK #-} !Int
, _scheduleWorkId :: (WorkerId -> m a) -> m ()
, _terminate :: a -> m a
, _terminateWith :: a -> m a
}
data SchedulerWS s m a = SchedulerWS
{ _workerStates :: !(WorkerStates s)
, _getScheduler :: !(Scheduler m a)
}
data WorkerStates s = WorkerStates
{ _workerStatesComp :: !Comp
, _workerStatesArray :: !(Array s)
, _workerStatesMutex :: !(IORef Bool)
}
data SchedulerOutcome a
= SchedulerFinished
| SchedulerTerminatedEarly !(Results a)
| SchedulerWorkerException WorkerException
newtype WorkerException =
WorkerException SomeException
deriving (Show)
instance Exception WorkerException
data WorkerTerminateException =
WorkerTerminateException
deriving (Show)
instance Exception WorkerTerminateException
data MutexException =
MutexException
deriving (Eq, Show)
instance Exception MutexException where
displayException MutexException =
"MutexException: WorkerStates cannot be used at the same time by different schedulers"