{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Livy.Client.Batch.GetBatch
(
GetBatch (..)
, getBatch
, gbBatchId
, GetBatchResponse (..)
, gbrBatch
) where
import Control.Lens
import Data.Aeson.TH
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 GetBatch = GetBatch
{ _gbBatchId :: BatchId
} deriving (Eq, Show, Typeable)
makeLenses ''GetBatch
instance ToPath GetBatch where
toPath r = toPath ["batches", toText $ r ^. gbBatchId]
instance LivyRequest GetBatch where
request = get
getBatch :: BatchId -> GetBatch
getBatch = GetBatch
newtype GetBatchResponse = GetBatchResponse
{ _gbrBatch :: Batch
} deriving (Eq, Show, Typeable)
makeLenses ''GetBatchResponse
deriveFromJSON ((recordPrefixOptions 3) { unwrapUnaryRecords = True }) ''GetBatchResponse
type instance LivyResponse GetBatch = GetBatchResponse