{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Network.Livy.Client.Types.Batch
(
Batch (..)
, BatchId (..)
, BatchState (..)
, BatchAppInfo
, bId
, bAppId
, bAppInfo
, bLog
, bState
) where
import Control.Lens
import Data.Aeson
import Data.Aeson.TH
import qualified Data.HashMap.Strict as Map
import Data.Text (Text)
import qualified Data.Text as T
import Data.Typeable
import Network.Livy.Client.Internal.JSON
import Network.Livy.Internal.Text
newtype BatchId = BatchId Int
deriving (Eq, Show, Typeable, ToText, ToJSON, FromJSON)
type BatchAppInfo = Map.HashMap Text (Maybe Text)
data BatchState
= BatchNotStarted
| BatchStarting
| BatchRecovering
| BatchIdle
| BatchRunning
| BatchBusy
| BatchShuttingDown
| BatchError
| BatchDead
| BatchKilled
| BatchSuccess
deriving (Bounded, Enum, Eq, Show, Typeable)
instance ToText BatchState where
toText BatchNotStarted = "not_started"
toText BatchStarting = "starting"
toText BatchRecovering = "recovering"
toText BatchIdle = "idle"
toText BatchRunning = "running"
toText BatchBusy = "busy"
toText BatchShuttingDown = "shutting_down"
toText BatchError = "error"
toText BatchDead = "dead"
toText BatchKilled = "killed"
toText BatchSuccess = "success"
instance ToJSON BatchState where
toJSON = String . toText
instance FromJSON BatchState where
parseJSON = withText "BatchState" $ \t ->
case lookup t toTextLookup of
Just st -> return st
Nothing -> fail . T.unpack $ "Unknown batch state: " <> t
data Batch = Batch
{ _bId :: !BatchId
, _bAppId :: !(Maybe Text)
, _bAppInfo :: !BatchAppInfo
, _bLog :: ![Text]
, _bState :: !BatchState
} deriving (Eq, Show, Typeable)
makeLenses ''Batch
deriveJSON (recordPrefixOptions 2) ''Batch