{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Livy.Client.Batch.KillBatch
(
KillBatch (..)
, killBatch
, kbBatchId
, KillBatchResponse (..)
, kbrMsg
) 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.Batch
import Network.Livy.Internal.Text
import Network.Livy.Request
import Network.Livy.Types
newtype KillBatch = KillBatch
{ _kbBatchId :: BatchId
} deriving (Eq, Show, Typeable)
makeLenses ''KillBatch
instance ToPath KillBatch where
toPath s = toPath ["batches", toText $ s ^. kbBatchId]
instance LivyRequest KillBatch where
request = delete
killBatch :: BatchId -> KillBatch
killBatch = KillBatch
newtype KillBatchResponse = KillBatchResponse
{ _kbrMsg :: Text
} deriving (Eq, Show, Typeable)
makeLenses ''KillBatchResponse
deriveFromJSON (recordPrefixOptions 4) ''KillBatchResponse
type instance LivyResponse KillBatch = KillBatchResponse