{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE RecordWildCards #-} module Periodic.Types.Job ( FuncName (..) , JobName (..) , Workload (..) , JobHandle , Job , initJob , setWorkload , setSchedAt , setCount , setTimeout , getFuncName , getName , getWorkload , getSchedAt , getCount , getTimeout , getHandle , unHandle , jobHandle ) where import Data.Byteable (Byteable (..)) import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as B (empty, length) import Data.ByteString.Lazy (toStrict) import Data.Hashable import Data.Int (Int64) import GHC.Generics (Generic) import Data.String (IsString (..)) import Periodic.Types.Internal import Data.Binary import Data.Binary.Get import Data.Binary.Put newtype FuncName = FuncName {FuncName -> ByteString unFN :: ByteString} deriving ((forall x. FuncName -> Rep FuncName x) -> (forall x. Rep FuncName x -> FuncName) -> Generic FuncName forall x. Rep FuncName x -> FuncName forall x. FuncName -> Rep FuncName x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep FuncName x -> FuncName $cfrom :: forall x. FuncName -> Rep FuncName x Generic, FuncName -> FuncName -> Bool (FuncName -> FuncName -> Bool) -> (FuncName -> FuncName -> Bool) -> Eq FuncName forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: FuncName -> FuncName -> Bool $c/= :: FuncName -> FuncName -> Bool == :: FuncName -> FuncName -> Bool $c== :: FuncName -> FuncName -> Bool Eq, Eq FuncName Eq FuncName => (FuncName -> FuncName -> Ordering) -> (FuncName -> FuncName -> Bool) -> (FuncName -> FuncName -> Bool) -> (FuncName -> FuncName -> Bool) -> (FuncName -> FuncName -> Bool) -> (FuncName -> FuncName -> FuncName) -> (FuncName -> FuncName -> FuncName) -> Ord FuncName FuncName -> FuncName -> Bool FuncName -> FuncName -> Ordering FuncName -> FuncName -> FuncName forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: FuncName -> FuncName -> FuncName $cmin :: FuncName -> FuncName -> FuncName max :: FuncName -> FuncName -> FuncName $cmax :: FuncName -> FuncName -> FuncName >= :: FuncName -> FuncName -> Bool $c>= :: FuncName -> FuncName -> Bool > :: FuncName -> FuncName -> Bool $c> :: FuncName -> FuncName -> Bool <= :: FuncName -> FuncName -> Bool $c<= :: FuncName -> FuncName -> Bool < :: FuncName -> FuncName -> Bool $c< :: FuncName -> FuncName -> Bool compare :: FuncName -> FuncName -> Ordering $ccompare :: FuncName -> FuncName -> Ordering $cp1Ord :: Eq FuncName Ord, Int -> FuncName -> ShowS [FuncName] -> ShowS FuncName -> String (Int -> FuncName -> ShowS) -> (FuncName -> String) -> ([FuncName] -> ShowS) -> Show FuncName forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [FuncName] -> ShowS $cshowList :: [FuncName] -> ShowS show :: FuncName -> String $cshow :: FuncName -> String showsPrec :: Int -> FuncName -> ShowS $cshowsPrec :: Int -> FuncName -> ShowS Show) instance Hashable FuncName instance IsString FuncName where fromString :: String -> FuncName fromString = ByteString -> FuncName FuncName (ByteString -> FuncName) -> (String -> ByteString) -> String -> FuncName forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ByteString forall a. IsString a => String -> a fromString instance FromBS FuncName where fromBS :: ByteString -> FuncName fromBS = ByteString -> FuncName FuncName (ByteString -> FuncName) -> (ByteString -> ByteString) -> ByteString -> FuncName forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString forall a. FromBS a => ByteString -> a fromBS instance Binary FuncName where get :: Get FuncName get = do Word8 size <- Get Word8 getWord8 ByteString dat <- Int -> Get ByteString getByteString (Int -> Get ByteString) -> Int -> Get ByteString forall a b. (a -> b) -> a -> b $ Word8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Word8 size FuncName -> Get FuncName forall (m :: * -> *) a. Monad m => a -> m a return (FuncName -> Get FuncName) -> FuncName -> Get FuncName forall a b. (a -> b) -> a -> b $ ByteString -> FuncName FuncName ByteString dat put :: FuncName -> Put put (FuncName dat :: ByteString dat) = do Word8 -> Put putWord8 (Word8 -> Put) -> (Int -> Word8) -> Int -> Put forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> Put) -> Int -> Put forall a b. (a -> b) -> a -> b $ ByteString -> Int B.length ByteString dat ByteString -> Put putByteString ByteString dat instance Validatable FuncName where validate :: FuncName -> Either String () validate (FuncName n :: ByteString n) = String -> Int32 -> Int32 -> Int -> Either String () validateLength "FuncName" 1 255 (Int -> Either String ()) -> Int -> Either String () forall a b. (a -> b) -> a -> b $ ByteString -> Int B.length ByteString n newtype JobName = JobName {JobName -> ByteString unJN :: ByteString} deriving ((forall x. JobName -> Rep JobName x) -> (forall x. Rep JobName x -> JobName) -> Generic JobName forall x. Rep JobName x -> JobName forall x. JobName -> Rep JobName x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep JobName x -> JobName $cfrom :: forall x. JobName -> Rep JobName x Generic, JobName -> JobName -> Bool (JobName -> JobName -> Bool) -> (JobName -> JobName -> Bool) -> Eq JobName forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: JobName -> JobName -> Bool $c/= :: JobName -> JobName -> Bool == :: JobName -> JobName -> Bool $c== :: JobName -> JobName -> Bool Eq, Eq JobName Eq JobName => (JobName -> JobName -> Ordering) -> (JobName -> JobName -> Bool) -> (JobName -> JobName -> Bool) -> (JobName -> JobName -> Bool) -> (JobName -> JobName -> Bool) -> (JobName -> JobName -> JobName) -> (JobName -> JobName -> JobName) -> Ord JobName JobName -> JobName -> Bool JobName -> JobName -> Ordering JobName -> JobName -> JobName forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: JobName -> JobName -> JobName $cmin :: JobName -> JobName -> JobName max :: JobName -> JobName -> JobName $cmax :: JobName -> JobName -> JobName >= :: JobName -> JobName -> Bool $c>= :: JobName -> JobName -> Bool > :: JobName -> JobName -> Bool $c> :: JobName -> JobName -> Bool <= :: JobName -> JobName -> Bool $c<= :: JobName -> JobName -> Bool < :: JobName -> JobName -> Bool $c< :: JobName -> JobName -> Bool compare :: JobName -> JobName -> Ordering $ccompare :: JobName -> JobName -> Ordering $cp1Ord :: Eq JobName Ord, Int -> JobName -> ShowS [JobName] -> ShowS JobName -> String (Int -> JobName -> ShowS) -> (JobName -> String) -> ([JobName] -> ShowS) -> Show JobName forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [JobName] -> ShowS $cshowList :: [JobName] -> ShowS show :: JobName -> String $cshow :: JobName -> String showsPrec :: Int -> JobName -> ShowS $cshowsPrec :: Int -> JobName -> ShowS Show) instance Hashable JobName instance IsString JobName where fromString :: String -> JobName fromString = ByteString -> JobName JobName (ByteString -> JobName) -> (String -> ByteString) -> String -> JobName forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ByteString forall a. IsString a => String -> a fromString instance FromBS JobName where fromBS :: ByteString -> JobName fromBS = ByteString -> JobName JobName (ByteString -> JobName) -> (ByteString -> ByteString) -> ByteString -> JobName forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString forall a. FromBS a => ByteString -> a fromBS instance Binary JobName where get :: Get JobName get = do Word8 size <- Get Word8 getWord8 ByteString dat <- Int -> Get ByteString getByteString (Int -> Get ByteString) -> Int -> Get ByteString forall a b. (a -> b) -> a -> b $ Word8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Word8 size JobName -> Get JobName forall (m :: * -> *) a. Monad m => a -> m a return (JobName -> Get JobName) -> JobName -> Get JobName forall a b. (a -> b) -> a -> b $ ByteString -> JobName JobName ByteString dat put :: JobName -> Put put (JobName dat :: ByteString dat) = do Word8 -> Put putWord8 (Word8 -> Put) -> (Int -> Word8) -> Int -> Put forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> Put) -> Int -> Put forall a b. (a -> b) -> a -> b $ ByteString -> Int B.length ByteString dat ByteString -> Put putByteString ByteString dat instance Validatable JobName where validate :: JobName -> Either String () validate (JobName n :: ByteString n) = String -> Int32 -> Int32 -> Int -> Either String () validateLength "JobName" 1 255 (Int -> Either String ()) -> Int -> Either String () forall a b. (a -> b) -> a -> b $ ByteString -> Int B.length ByteString n data JobHandle = JobHandle FuncName JobName deriving ((forall x. JobHandle -> Rep JobHandle x) -> (forall x. Rep JobHandle x -> JobHandle) -> Generic JobHandle forall x. Rep JobHandle x -> JobHandle forall x. JobHandle -> Rep JobHandle x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep JobHandle x -> JobHandle $cfrom :: forall x. JobHandle -> Rep JobHandle x Generic, JobHandle -> JobHandle -> Bool (JobHandle -> JobHandle -> Bool) -> (JobHandle -> JobHandle -> Bool) -> Eq JobHandle forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: JobHandle -> JobHandle -> Bool $c/= :: JobHandle -> JobHandle -> Bool == :: JobHandle -> JobHandle -> Bool $c== :: JobHandle -> JobHandle -> Bool Eq, Eq JobHandle Eq JobHandle => (JobHandle -> JobHandle -> Ordering) -> (JobHandle -> JobHandle -> Bool) -> (JobHandle -> JobHandle -> Bool) -> (JobHandle -> JobHandle -> Bool) -> (JobHandle -> JobHandle -> Bool) -> (JobHandle -> JobHandle -> JobHandle) -> (JobHandle -> JobHandle -> JobHandle) -> Ord JobHandle JobHandle -> JobHandle -> Bool JobHandle -> JobHandle -> Ordering JobHandle -> JobHandle -> JobHandle forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: JobHandle -> JobHandle -> JobHandle $cmin :: JobHandle -> JobHandle -> JobHandle max :: JobHandle -> JobHandle -> JobHandle $cmax :: JobHandle -> JobHandle -> JobHandle >= :: JobHandle -> JobHandle -> Bool $c>= :: JobHandle -> JobHandle -> Bool > :: JobHandle -> JobHandle -> Bool $c> :: JobHandle -> JobHandle -> Bool <= :: JobHandle -> JobHandle -> Bool $c<= :: JobHandle -> JobHandle -> Bool < :: JobHandle -> JobHandle -> Bool $c< :: JobHandle -> JobHandle -> Bool compare :: JobHandle -> JobHandle -> Ordering $ccompare :: JobHandle -> JobHandle -> Ordering $cp1Ord :: Eq JobHandle Ord, Int -> JobHandle -> ShowS [JobHandle] -> ShowS JobHandle -> String (Int -> JobHandle -> ShowS) -> (JobHandle -> String) -> ([JobHandle] -> ShowS) -> Show JobHandle forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [JobHandle] -> ShowS $cshowList :: [JobHandle] -> ShowS show :: JobHandle -> String $cshow :: JobHandle -> String showsPrec :: Int -> JobHandle -> ShowS $cshowsPrec :: Int -> JobHandle -> ShowS Show) instance Hashable JobHandle instance Binary JobHandle where get :: Get JobHandle get = do FuncName fn <- Get FuncName forall t. Binary t => Get t get FuncName -> JobName -> JobHandle JobHandle FuncName fn (JobName -> JobHandle) -> Get JobName -> Get JobHandle forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get JobName forall t. Binary t => Get t get put :: JobHandle -> Put put (JobHandle fn :: FuncName fn jn :: JobName jn) = do FuncName -> Put forall t. Binary t => t -> Put put FuncName fn JobName -> Put forall t. Binary t => t -> Put put JobName jn instance Validatable JobHandle where validate :: JobHandle -> Either String () validate (JobHandle fn :: FuncName fn jn :: JobName jn) = do FuncName -> Either String () forall a. Validatable a => a -> Either String () validate FuncName fn JobName -> Either String () forall a. Validatable a => a -> Either String () validate JobName jn newtype Workload = Workload {Workload -> ByteString unWL :: ByteString} deriving ((forall x. Workload -> Rep Workload x) -> (forall x. Rep Workload x -> Workload) -> Generic Workload forall x. Rep Workload x -> Workload forall x. Workload -> Rep Workload x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Workload x -> Workload $cfrom :: forall x. Workload -> Rep Workload x Generic, Workload -> Workload -> Bool (Workload -> Workload -> Bool) -> (Workload -> Workload -> Bool) -> Eq Workload forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Workload -> Workload -> Bool $c/= :: Workload -> Workload -> Bool == :: Workload -> Workload -> Bool $c== :: Workload -> Workload -> Bool Eq, Eq Workload Eq Workload => (Workload -> Workload -> Ordering) -> (Workload -> Workload -> Bool) -> (Workload -> Workload -> Bool) -> (Workload -> Workload -> Bool) -> (Workload -> Workload -> Bool) -> (Workload -> Workload -> Workload) -> (Workload -> Workload -> Workload) -> Ord Workload Workload -> Workload -> Bool Workload -> Workload -> Ordering Workload -> Workload -> Workload forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Workload -> Workload -> Workload $cmin :: Workload -> Workload -> Workload max :: Workload -> Workload -> Workload $cmax :: Workload -> Workload -> Workload >= :: Workload -> Workload -> Bool $c>= :: Workload -> Workload -> Bool > :: Workload -> Workload -> Bool $c> :: Workload -> Workload -> Bool <= :: Workload -> Workload -> Bool $c<= :: Workload -> Workload -> Bool < :: Workload -> Workload -> Bool $c< :: Workload -> Workload -> Bool compare :: Workload -> Workload -> Ordering $ccompare :: Workload -> Workload -> Ordering $cp1Ord :: Eq Workload Ord, Int -> Workload -> ShowS [Workload] -> ShowS Workload -> String (Int -> Workload -> ShowS) -> (Workload -> String) -> ([Workload] -> ShowS) -> Show Workload forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Workload] -> ShowS $cshowList :: [Workload] -> ShowS show :: Workload -> String $cshow :: Workload -> String showsPrec :: Int -> Workload -> ShowS $cshowsPrec :: Int -> Workload -> ShowS Show) instance Hashable Workload instance IsString Workload where fromString :: String -> Workload fromString = ByteString -> Workload Workload (ByteString -> Workload) -> (String -> ByteString) -> String -> Workload forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ByteString forall a. IsString a => String -> a fromString instance FromBS Workload where fromBS :: ByteString -> Workload fromBS = ByteString -> Workload Workload (ByteString -> Workload) -> (ByteString -> ByteString) -> ByteString -> Workload forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString forall a. FromBS a => ByteString -> a fromBS instance Binary Workload where get :: Get Workload get = do Word32 size <- Get Word32 getWord32be ByteString dat <- Int -> Get ByteString getByteString (Int -> Get ByteString) -> Int -> Get ByteString forall a b. (a -> b) -> a -> b $ Word32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 size Workload -> Get Workload forall (m :: * -> *) a. Monad m => a -> m a return (Workload -> Get Workload) -> Workload -> Get Workload forall a b. (a -> b) -> a -> b $ ByteString -> Workload Workload ByteString dat put :: Workload -> Put put (Workload dat :: ByteString dat) = do Word32 -> Put putWord32be (Word32 -> Put) -> (Int -> Word32) -> Int -> Put forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> Put) -> Int -> Put forall a b. (a -> b) -> a -> b $ ByteString -> Int B.length ByteString dat ByteString -> Put putByteString ByteString dat instance Validatable Workload where validate :: Workload -> Either String () validate (Workload n :: ByteString n) = String -> Int32 -> Int32 -> Int -> Either String () validateLength "Workload" 0 Int32 forall a. Bounded a => a maxBound (Int -> Either String ()) -> Int -> Either String () forall a b. (a -> b) -> a -> b $ ByteString -> Int B.length ByteString n data Job = Job { Job -> FuncName jFuncName :: FuncName , Job -> JobName jName :: JobName , Job -> Workload jWorkload :: Workload , Job -> Int64 jSchedAt :: Int64 , Job -> Int jCount :: Int , Job -> Int jTimeout :: Int } deriving (Int -> Job -> ShowS [Job] -> ShowS Job -> String (Int -> Job -> ShowS) -> (Job -> String) -> ([Job] -> ShowS) -> Show Job forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Job] -> ShowS $cshowList :: [Job] -> ShowS show :: Job -> String $cshow :: Job -> String showsPrec :: Int -> Job -> ShowS $cshowsPrec :: Int -> Job -> ShowS Show) instance Byteable Job where toBytes :: Job -> ByteString toBytes = ByteString -> ByteString toStrict (ByteString -> ByteString) -> (Job -> ByteString) -> Job -> ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Job -> ByteString forall a. Binary a => a -> ByteString encode data JVer = V0 | V1 | V2 | V3 toVer :: Int -> JVer toVer :: Int -> JVer toVer 0 = JVer V0 toVer 1 = JVer V1 toVer 2 = JVer V2 toVer 3 = JVer V3 toVer _ = JVer V0 fromVer :: JVer -> Int fromVer :: JVer -> Int fromVer V0 = 0 fromVer V1 = 1 fromVer V2 = 2 fromVer V3 = 3 calcVer :: Job -> JVer calcVer :: Job -> JVer calcVer Job{jCount :: Job -> Int jCount = Int count, jTimeout :: Job -> Int jTimeout = Int to} | Int count Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > 0 Bool -> Bool -> Bool && Int to Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > 0 = JVer V3 | Int to Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > 0 = JVer V2 | Int count Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > 0 = JVer V1 | Bool otherwise = JVer V0 instance Binary Job where get :: Get Job get = do FuncName jFuncName <- Get FuncName forall t. Binary t => Get t get JobName jName <- Get JobName forall t. Binary t => Get t get Workload jWorkload <- Get Workload forall t. Binary t => Get t get Int64 jSchedAt <- Get Int64 getInt64be JVer ver <- Int -> JVer toVer (Int -> JVer) -> (Word8 -> Int) -> Word8 -> JVer forall b c a. (b -> c) -> (a -> b) -> a -> c . Word8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Word8 -> JVer) -> Get Word8 -> Get JVer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Word8 getWord8 (jCount :: Int jCount, jTimeout :: Int jTimeout) <- case JVer ver of V0 -> (Int, Int) -> Get (Int, Int) forall (f :: * -> *) a. Applicative f => a -> f a pure (0, 0) V1 -> do Int v <- Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int32 -> Int) -> Get Int32 -> Get Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Int32 getInt32be (Int, Int) -> Get (Int, Int) forall (f :: * -> *) a. Applicative f => a -> f a pure (Int v, 0) V2 -> do Int v <- Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int32 -> Int) -> Get Int32 -> Get Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Int32 getInt32be (Int, Int) -> Get (Int, Int) forall (f :: * -> *) a. Applicative f => a -> f a pure (0, Int v) V3 -> do Int v0 <- Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int32 -> Int) -> Get Int32 -> Get Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Int32 getInt32be Int v1 <- Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int32 -> Int) -> Get Int32 -> Get Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Int32 getInt32be (Int, Int) -> Get (Int, Int) forall (f :: * -> *) a. Applicative f => a -> f a pure (Int v0, Int v1) Job -> Get Job forall (m :: * -> *) a. Monad m => a -> m a return Job :: FuncName -> JobName -> Workload -> Int64 -> Int -> Int -> Job Job {..} put :: Job -> Put put j :: Job j@Job {..} = do FuncName -> Put forall t. Binary t => t -> Put put FuncName jFuncName JobName -> Put forall t. Binary t => t -> Put put JobName jName Workload -> Put forall t. Binary t => t -> Put put Workload jWorkload Int64 -> Put putInt64be Int64 jSchedAt let ver :: JVer ver = Job -> JVer calcVer Job j Word8 -> Put putWord8 (Word8 -> Put) -> Word8 -> Put forall a b. (a -> b) -> a -> b $ Int -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> Word8) -> Int -> Word8 forall a b. (a -> b) -> a -> b $ JVer -> Int fromVer JVer ver case JVer ver of V0 -> () -> Put forall (f :: * -> *) a. Applicative f => a -> f a pure () V1 -> Int32 -> Put putInt32be (Int32 -> Put) -> Int32 -> Put forall a b. (a -> b) -> a -> b $ Int -> Int32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int jCount V2 -> Int32 -> Put putInt32be (Int32 -> Put) -> Int32 -> Put forall a b. (a -> b) -> a -> b $ Int -> Int32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int jTimeout V3 -> do Int32 -> Put putInt32be (Int32 -> Put) -> Int32 -> Put forall a b. (a -> b) -> a -> b $ Int -> Int32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int jCount Int32 -> Put putInt32be (Int32 -> Put) -> Int32 -> Put forall a b. (a -> b) -> a -> b $ Int -> Int32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int jTimeout instance Validatable Job where validate :: Job -> Either String () validate (Job fn :: FuncName fn jn :: JobName jn w :: Workload w _ c :: Int c t :: Int t) = do FuncName -> Either String () forall a. Validatable a => a -> Either String () validate FuncName fn JobName -> Either String () forall a. Validatable a => a -> Either String () validate JobName jn Workload -> Either String () forall a. Validatable a => a -> Either String () validate Workload w String -> Int -> Int -> Int -> Either String () forall a. Ord a => String -> a -> a -> a -> Either String () validateNum "JobCount" 0 Int forall a. Bounded a => a maxBound Int c String -> Int -> Int -> Int -> Either String () forall a. Ord a => String -> a -> a -> a -> Either String () validateNum "JobTimeout" 0 Int forall a. Bounded a => a maxBound Int t initJob :: FuncName -> JobName -> Job initJob :: FuncName -> JobName -> Job initJob jFuncName :: FuncName jFuncName jName :: JobName jName = Job :: FuncName -> JobName -> Workload -> Int64 -> Int -> Int -> Job Job { jWorkload :: Workload jWorkload = ByteString -> Workload Workload ByteString B.empty , jSchedAt :: Int64 jSchedAt = 0 , jCount :: Int jCount = 0 , jTimeout :: Int jTimeout = 0 , .. } setSchedAt :: Int64 -> Job -> Job setSchedAt :: Int64 -> Job -> Job setSchedAt schedAt :: Int64 schedAt job :: Job job = Job job {jSchedAt :: Int64 jSchedAt = Int64 schedAt} setWorkload :: Workload -> Job -> Job setWorkload :: Workload -> Job -> Job setWorkload w :: Workload w job :: Job job = Job job {jWorkload :: Workload jWorkload = Workload w} setCount :: Int -> Job -> Job setCount :: Int -> Job -> Job setCount c :: Int c job :: Job job = Job job {jCount :: Int jCount = Int c} setTimeout :: Int -> Job -> Job setTimeout :: Int -> Job -> Job setTimeout t :: Int t job :: Job job = Job job {jTimeout :: Int jTimeout = Int t} getFuncName :: Job -> FuncName getFuncName :: Job -> FuncName getFuncName = Job -> FuncName jFuncName getName :: Job -> JobName getName :: Job -> JobName getName = Job -> JobName jName getSchedAt :: Job -> Int64 getSchedAt :: Job -> Int64 getSchedAt = Job -> Int64 jSchedAt getWorkload :: Job -> Workload getWorkload :: Job -> Workload getWorkload = Job -> Workload jWorkload getCount :: Job -> Int getCount :: Job -> Int getCount = Job -> Int jCount getTimeout :: Job -> Int getTimeout :: Job -> Int getTimeout = Job -> Int jTimeout getHandle :: Job -> JobHandle getHandle :: Job -> JobHandle getHandle job :: Job job = FuncName -> JobName -> JobHandle jobHandle (Job -> FuncName getFuncName Job job) (Job -> JobName getName Job job) unHandle :: JobHandle -> (FuncName, JobName) unHandle :: JobHandle -> (FuncName, JobName) unHandle (JobHandle fn :: FuncName fn jn :: JobName jn) = (FuncName fn, JobName jn) jobHandle :: FuncName -> JobName -> JobHandle jobHandle :: FuncName -> JobName -> JobHandle jobHandle = FuncName -> JobName -> JobHandle JobHandle