{-# LANGUAGE OverloadedStrings #-} module Periodic.Types.ClientCommand ( ClientCommand (..) ) where import Data.Binary import Data.Binary.Get (getWord32be) import Data.Binary.Put (putWord32be) import Periodic.Types.Internal import Periodic.Types.Job (FuncName, Job, JobName) data ClientCommand = SubmitJob Job | Status | Ping | DropFunc FuncName | RemoveJob FuncName JobName | ConfigGet ConfigKey | ConfigSet ConfigKey Int | Dump | Load [Job] | Shutdown | RunJob Job deriving (Int -> ClientCommand -> ShowS [ClientCommand] -> ShowS ClientCommand -> String (Int -> ClientCommand -> ShowS) -> (ClientCommand -> String) -> ([ClientCommand] -> ShowS) -> Show ClientCommand forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ClientCommand] -> ShowS $cshowList :: [ClientCommand] -> ShowS show :: ClientCommand -> String $cshow :: ClientCommand -> String showsPrec :: Int -> ClientCommand -> ShowS $cshowsPrec :: Int -> ClientCommand -> ShowS Show) instance Binary ClientCommand where get :: Get ClientCommand get = do Word8 tp <- Get Word8 getWord8 case Word8 tp of 13 -> Job -> ClientCommand SubmitJob (Job -> ClientCommand) -> Get Job -> Get ClientCommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Job forall t. Binary t => Get t get 14 -> ClientCommand -> Get ClientCommand forall (f :: * -> *) a. Applicative f => a -> f a pure ClientCommand Status 9 -> ClientCommand -> Get ClientCommand forall (f :: * -> *) a. Applicative f => a -> f a pure ClientCommand Ping 15 -> FuncName -> ClientCommand DropFunc (FuncName -> ClientCommand) -> Get FuncName -> Get ClientCommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get FuncName forall t. Binary t => Get t get 17 -> do FuncName fn <- Get FuncName forall t. Binary t => Get t get FuncName -> JobName -> ClientCommand RemoveJob FuncName fn (JobName -> ClientCommand) -> Get JobName -> Get ClientCommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get JobName forall t. Binary t => Get t get 20 -> ClientCommand -> Get ClientCommand forall (f :: * -> *) a. Applicative f => a -> f a pure ClientCommand Shutdown 22 -> ConfigKey -> ClientCommand ConfigGet (ConfigKey -> ClientCommand) -> Get ConfigKey -> Get ClientCommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get ConfigKey forall t. Binary t => Get t get 23 -> do ConfigKey key <- Get ConfigKey forall t. Binary t => Get t get Word32 val <- Get Word32 getWord32be ClientCommand -> Get ClientCommand forall (f :: * -> *) a. Applicative f => a -> f a pure (ClientCommand -> Get ClientCommand) -> (Int -> ClientCommand) -> Int -> Get ClientCommand forall b c a. (b -> c) -> (a -> b) -> a -> c . ConfigKey -> Int -> ClientCommand ConfigSet ConfigKey key (Int -> Get ClientCommand) -> Int -> Get ClientCommand forall a b. (a -> b) -> a -> b $ Word32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 val 18 -> ClientCommand -> Get ClientCommand forall (f :: * -> *) a. Applicative f => a -> f a pure ClientCommand Dump 19 -> [Job] -> ClientCommand Load ([Job] -> ClientCommand) -> Get [Job] -> Get ClientCommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get [Job] forall t. Binary t => Get t get 25 -> Job -> ClientCommand RunJob (Job -> ClientCommand) -> Get Job -> Get ClientCommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Job forall t. Binary t => Get t get _ -> String -> Get ClientCommand forall a. HasCallStack => String -> a error (String -> Get ClientCommand) -> String -> Get ClientCommand forall a b. (a -> b) -> a -> b $ "Error ClientCommand" String -> ShowS forall a. [a] -> [a] -> [a] ++ Word8 -> String forall a. Show a => a -> String show Word8 tp put :: ClientCommand -> Put put (SubmitJob job :: Job job) = do Word8 -> Put putWord8 13 Job -> Put forall t. Binary t => t -> Put put Job job put Status = Word8 -> Put putWord8 14 put Ping = Word8 -> Put putWord8 9 put (DropFunc func :: FuncName func) = do Word8 -> Put putWord8 15 FuncName -> Put forall t. Binary t => t -> Put put FuncName func put (RemoveJob fn :: FuncName fn jn :: JobName jn) = do Word8 -> Put putWord8 17 FuncName -> Put forall t. Binary t => t -> Put put FuncName fn JobName -> Put forall t. Binary t => t -> Put put JobName jn put Shutdown = Word8 -> Put putWord8 20 put (ConfigGet key :: ConfigKey key) = do Word8 -> Put putWord8 22 ConfigKey -> Put forall t. Binary t => t -> Put put ConfigKey key put (ConfigSet k :: ConfigKey k v :: Int v) = do Word8 -> Put putWord8 23 ConfigKey -> Put forall t. Binary t => t -> Put put ConfigKey k Word32 -> Put putWord32be (Word32 -> Put) -> Word32 -> Put forall a b. (a -> b) -> a -> b $ Int -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int v put Dump = Word8 -> Put putWord8 18 put (Load jobs :: [Job] jobs) = do Word8 -> Put putWord8 19 [Job] -> Put forall t. Binary t => t -> Put put [Job] jobs put (RunJob job :: Job job) = do Word8 -> Put putWord8 25 Job -> Put forall t. Binary t => t -> Put put Job job instance Validatable ClientCommand where validate :: ClientCommand -> Either String () validate (SubmitJob job :: Job job) = Job -> Either String () forall a. Validatable a => a -> Either String () validate Job job validate (DropFunc func :: FuncName func) = FuncName -> Either String () forall a. Validatable a => a -> Either String () validate FuncName func validate (RemoveJob 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 validate (ConfigGet key :: ConfigKey key) = ConfigKey -> Either String () forall a. Validatable a => a -> Either String () validate ConfigKey key validate (ConfigSet k :: ConfigKey k v :: Int v) = do ConfigKey -> Either String () forall a. Validatable a => a -> Either String () validate ConfigKey k String -> Int -> Int -> Int -> Either String () forall a. Ord a => String -> a -> a -> a -> Either String () validateNum "ConfigValue" 0 0xFFFFFFFF Int v validate (Load jobs :: [Job] jobs) = [Job] -> Either String () forall a. Validatable a => a -> Either String () validate [Job] jobs validate (RunJob job :: Job job) = Job -> Either String () forall a. Validatable a => a -> Either String () validate Job job validate _ = () -> Either String () forall a b. b -> Either a b Right ()