{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Network.Livy.Client.Types.Session
(
Session (..)
, SessionId (..)
, SessionKind (..)
, SessionState (..)
, SessionAppInfo
, sId
, sAppId
, sOwner
, sProxyUser
, sKind
, sLog
, sState
, sAppInfo
) 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
data SessionKind
= SparkSession
| PySparkSession
| SparkRSession
| SQLSession
| SharedSession
deriving (Bounded, Enum, Eq, Show, Typeable)
instance ToText SessionKind where
toText = T.toLower . T.reverse . T.drop 7 . T.reverse . T.pack . show
instance ToJSON SessionKind where
toJSON = String . toText
instance FromJSON SessionKind where
parseJSON = withText "SessionKind" $ \t ->
case lookup t toTextLookup of
Just sk -> return sk
Nothing -> fail . T.unpack $ "Unknown session type: " <> t
data SessionState
= SessionNotStarted
| SessionStarting
| SessionRecovering
| SessionIdle
| SessionRunning
| SessionBusy
| SessionShuttingDown
| SessionError
| SessionDead
| SessionKilled
| SessionSuccess
deriving (Bounded, Enum, Eq, Show, Typeable)
instance ToText SessionState where
toText SessionNotStarted = "not_started"
toText SessionStarting = "starting"
toText SessionRecovering = "recovering"
toText SessionIdle = "idle"
toText SessionRunning = "running"
toText SessionBusy = "busy"
toText SessionShuttingDown = "shutting_down"
toText SessionError = "error"
toText SessionDead = "dead"
toText SessionKilled = "killed"
toText SessionSuccess = "success"
instance ToJSON SessionState where
toJSON = String . toText
instance FromJSON SessionState where
parseJSON = withText "SessionState" $ \t ->
case lookup t toTextLookup of
Just st -> return st
Nothing -> fail . T.unpack $ "Unknown session state: " <> t
newtype SessionId = SessionId Int
deriving (Eq, Show, Typeable, ToText, ToJSON, FromJSON)
type SessionAppInfo = Map.HashMap Text (Maybe Text)
data Session = Session
{ _sId :: !SessionId
, _sAppId :: !(Maybe Text)
, _sOwner :: !(Maybe Text)
, _sProxyUser :: !(Maybe Text)
, _sKind :: !SessionKind
, _sLog :: ![Text]
, _sState :: !SessionState
, _sAppInfo :: !SessionAppInfo
} deriving (Eq, Show, Typeable)
makeLenses ''Session
deriveJSON (recordPrefixOptions 2) ''Session