{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Livy.Client.Interactive.GetSessions
(
GetSessions (..)
, getSessions
, gssFrom
, gssSize
, GetSessionsResponse (..)
, gssrFrom
, gssrSize
, gssrSessions
) where
import Control.Lens
import Data.Aeson.TH
import qualified Data.ByteString.Char8 as C
import Data.Maybe (isJust)
import Data.Typeable
import Network.Livy.Client.Internal.JSON
import Network.Livy.Client.Types.Session
import Network.Livy.Request
import Network.Livy.Types
data GetSessions = GetSessions
{ _gssFrom :: Maybe Int
, _gssSize :: Maybe Int
} deriving (Eq, Show, Typeable)
makeLenses ''GetSessions
instance ToPath GetSessions where
toPath = const "sessions"
instance ToQuery GetSessions where
toQueryString r = filter (isJust . snd)
[ ("from", C.pack . show <$> r ^. gssFrom)
, ("size", C.pack . show <$> r ^. gssSize)
]
instance LivyRequest GetSessions where
request = getQuery
getSessions :: GetSessions
getSessions = GetSessions Nothing Nothing
data GetSessionsResponse = GetSessionsResponse
{ _gssrFrom :: !Int
, _gssrSize :: !(Maybe Int)
, _gssrSessions :: ![Session]
} deriving (Eq, Show, Typeable)
makeLenses ''GetSessionsResponse
deriveFromJSON (recordPrefixOptions 5) ''GetSessionsResponse
type instance LivyResponse GetSessions = GetSessionsResponse