{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Livy.Client.Interactive.GetSession
(
GetSession (..)
, getSession
, gsSessionId
, GetSessionResponse (..)
, gsrSession
) where
import Control.Lens
import Data.Aeson.TH
import Data.Typeable
import Network.Livy.Client.Internal.JSON
import Network.Livy.Client.Types.Session
import Network.Livy.Internal.Text
import Network.Livy.Request
import Network.Livy.Types
newtype GetSession = GetSession
{ _gsSessionId :: SessionId
} deriving (Eq, Show, Typeable)
makeLenses ''GetSession
instance ToPath GetSession where
toPath r = toPath ["sessions", toText $ r ^. gsSessionId]
instance LivyRequest GetSession where
request = get
getSession :: SessionId -> GetSession
getSession = GetSession
newtype GetSessionResponse = GetSessionResponse
{ _gsrSession :: Session
} deriving (Eq, Show, Typeable)
makeLenses ''GetSessionResponse
deriveFromJSON ((recordPrefixOptions 3) { unwrapUnaryRecords = True }) ''GetSessionResponse
type instance LivyResponse GetSession = GetSessionResponse