{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Livy.Client.Interactive.CreateSession
(
CreateSession (..)
, createSession
, csKind
, csProxyUser
, csJars
, csPyFiles
, csFiles
, csDriverMemory
, csDriverCores
, csExecutorMemory
, csExecutorCores
, csNumExecutors
, csArchives
, csQueue
, csName
, csConf
, csHeartbeatTimeoutInSecond
, CreateSessionResponse (..)
, csrSession
) where
import Control.Lens
import Data.Aeson.TH
import qualified Data.HashMap.Strict as Map
import Data.Text (Text)
import Data.Typeable
import Network.Livy.Client.Internal.JSON
import Network.Livy.Client.Types.Session
import Network.Livy.Request
import Network.Livy.Types
data CreateSession = CreateSession
{ _csKind :: Maybe SessionKind
, _csProxyUser :: Maybe Text
, _csJars :: Maybe [Text]
, _csPyFiles :: Maybe [Text]
, _csFiles :: Maybe [Text]
, _csDriverMemory :: Maybe Text
, _csDriverCores :: Maybe Int
, _csExecutorMemory :: Maybe Text
, _csExecutorCores :: Maybe Int
, _csNumExecutors :: Maybe Int
, _csArchives :: Maybe [Text]
, _csQueue :: Maybe Text
, _csName :: Maybe Text
, _csConf :: Maybe (Map.HashMap Text Text)
, _csHeartbeatTimeoutInSecond :: Maybe Int
} deriving (Eq, Show, Typeable)
makeLenses ''CreateSession
deriveToJSON ((recordPrefixOptions 3) { omitNothingFields = True }) ''CreateSession
instance ToPath CreateSession where
toPath = const "sessions"
instance LivyRequest CreateSession where
request = postJSON
createSession :: CreateSession
createSession = CreateSession
{ _csKind = Nothing
, _csProxyUser = Nothing
, _csJars = Nothing
, _csPyFiles = Nothing
, _csFiles = Nothing
, _csDriverMemory = Nothing
, _csDriverCores = Nothing
, _csExecutorMemory = Nothing
, _csExecutorCores = Nothing
, _csNumExecutors = Nothing
, _csArchives = Nothing
, _csQueue = Nothing
, _csName = Nothing
, _csConf = Nothing
, _csHeartbeatTimeoutInSecond = Nothing
}
newtype CreateSessionResponse = CreateSessionResponse
{ _csrSession :: Session
} deriving (Eq, Show, Typeable)
makeLenses ''CreateSessionResponse
deriveFromJSON (defaultOptions { unwrapUnaryRecords = True }) ''CreateSessionResponse
type instance LivyResponse CreateSession = CreateSessionResponse