{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Livy.Client.Interactive.RunStatementCompletion
(
RunStatementCompletion (..)
, runStatementCompletion
, rscSessionId
, rscCode
, rscKind
, rscCursor
, RunStatementCompletionResponse (..)
, rscrCandidates
) where
import Control.Lens
import Data.Aeson.TH
import Data.Text (Text)
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
data RunStatementCompletion = RunStatementCompletion
{ _rscSessionId :: SessionId
, _rscCode :: Maybe Text
, _rscKind :: Maybe SessionKind
, _rscCursor :: Maybe Text
} deriving (Eq, Show, Typeable)
makeLenses ''RunStatementCompletion
instance ToPath RunStatementCompletion where
toPath r = toPath ["sessions", toText $ r ^. rscSessionId, "completion"]
instance LivyRequest RunStatementCompletion where
request r = postBody r
[ ("code", toText $ r ^. rscCode)
, ("kind", toText $ r ^. rscKind)
, ("cursor", toText $ r ^. rscCursor)
]
runStatementCompletion :: SessionId -> RunStatementCompletion
runStatementCompletion sid = RunStatementCompletion sid Nothing Nothing Nothing
newtype RunStatementCompletionResponse = RunStatementCompletionResponse
{ _rscrCandidates :: [Text]
} deriving (Eq, Show, Typeable)
makeLenses ''RunStatementCompletionResponse
deriveFromJSON (recordPrefixOptions 5) ''RunStatementCompletionResponse
type instance LivyResponse RunStatementCompletion = RunStatementCompletionResponse