{- | Defines types used throughout the app -} {-# LANGUAGE ExistentialQuantification #-} module Web.JobsUi.Internal.Types ( module Web.JobsUi.Internal.Types , module Export ) where import Web.Spock import Data.Time import Control.Concurrent import Control.Concurrent.STM import qualified Data.Sequence as Seq import qualified Data.Text as T import qualified Lucid as H import Text.Digestive.Types as Export (Result(..)) import Web.JobsUi.Types as Export type Html = H.Html () data ServerState = ServerState { myjobsVar :: TVar Jobs , counterVar :: TVar Int } type Action ctx a = SpockActionCtx ctx () () ServerState a type Action' ctx = SpockActionCtx ctx () () ServerState type Jobs = JobsDS Job data JobsDS a = Jobs { waiting :: Seq.Seq a , running :: Maybe a , done :: [a] } deriving (Functor, Foldable, Traversable) noJobs :: Jobs noJobs = Jobs mempty Nothing mempty data Job = forall info. Job { jobId :: JobId , jobTimeQueued :: ZonedTime , jobTimeStarted :: Maybe ZonedTime , jobTimeEnded :: Maybe ZonedTime , jobFinished :: Maybe (Result T.Text T.Text) , jobThread :: Maybe ThreadId , jobPayload :: info , jobInfo :: JobInfo info } getJobType :: Job -> T.Text getJobType Job{..} = jiType jobInfo getJobParams :: Job -> [T.Text] getJobParams Job{..} = jiParams jobInfo $ jobPayload newtype JobId = JobId { getJobId :: Int } deriving (Eq, Ord) instance Show JobId where show (JobId i) = show i data JobStatus = Done | Running | Waiting deriving (Eq, Show)