module Claude.V1.Messages.Batches
(
CreateBatch(..)
, _CreateBatch
, BatchRequest(..)
, BatchObject(..)
, ProcessingStatus(..)
, RequestCounts(..)
, BatchResult(..)
, BatchResultType(..)
, ListBatchesResponse(..)
, API
) where
import Claude.Prelude
import Claude.V1.Messages (CreateMessage, MessageResponse)
import qualified Data.Aeson as Aeson
import qualified Data.Char as Char
import qualified Claude.V1.Error as Error
data BatchRequest = BatchRequest
{ BatchRequest -> Text
custom_id :: Text
, BatchRequest -> CreateMessage
params :: CreateMessage
} deriving stock ((forall x. BatchRequest -> Rep BatchRequest x)
-> (forall x. Rep BatchRequest x -> BatchRequest)
-> Generic BatchRequest
forall x. Rep BatchRequest x -> BatchRequest
forall x. BatchRequest -> Rep BatchRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BatchRequest -> Rep BatchRequest x
from :: forall x. BatchRequest -> Rep BatchRequest x
$cto :: forall x. Rep BatchRequest x -> BatchRequest
to :: forall x. Rep BatchRequest x -> BatchRequest
Generic, Int -> BatchRequest -> ShowS
[BatchRequest] -> ShowS
BatchRequest -> String
(Int -> BatchRequest -> ShowS)
-> (BatchRequest -> String)
-> ([BatchRequest] -> ShowS)
-> Show BatchRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BatchRequest -> ShowS
showsPrec :: Int -> BatchRequest -> ShowS
$cshow :: BatchRequest -> String
show :: BatchRequest -> String
$cshowList :: [BatchRequest] -> ShowS
showList :: [BatchRequest] -> ShowS
Show)
deriving anyclass (Maybe BatchRequest
Value -> Parser [BatchRequest]
Value -> Parser BatchRequest
(Value -> Parser BatchRequest)
-> (Value -> Parser [BatchRequest])
-> Maybe BatchRequest
-> FromJSON BatchRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser BatchRequest
parseJSON :: Value -> Parser BatchRequest
$cparseJSONList :: Value -> Parser [BatchRequest]
parseJSONList :: Value -> Parser [BatchRequest]
$comittedField :: Maybe BatchRequest
omittedField :: Maybe BatchRequest
FromJSON, [BatchRequest] -> Value
[BatchRequest] -> Encoding
BatchRequest -> Bool
BatchRequest -> Value
BatchRequest -> Encoding
(BatchRequest -> Value)
-> (BatchRequest -> Encoding)
-> ([BatchRequest] -> Value)
-> ([BatchRequest] -> Encoding)
-> (BatchRequest -> Bool)
-> ToJSON BatchRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: BatchRequest -> Value
toJSON :: BatchRequest -> Value
$ctoEncoding :: BatchRequest -> Encoding
toEncoding :: BatchRequest -> Encoding
$ctoJSONList :: [BatchRequest] -> Value
toJSONList :: [BatchRequest] -> Value
$ctoEncodingList :: [BatchRequest] -> Encoding
toEncodingList :: [BatchRequest] -> Encoding
$comitField :: BatchRequest -> Bool
omitField :: BatchRequest -> Bool
ToJSON)
data CreateBatch = CreateBatch
{ CreateBatch -> Vector BatchRequest
requests :: Vector BatchRequest
} deriving stock ((forall x. CreateBatch -> Rep CreateBatch x)
-> (forall x. Rep CreateBatch x -> CreateBatch)
-> Generic CreateBatch
forall x. Rep CreateBatch x -> CreateBatch
forall x. CreateBatch -> Rep CreateBatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateBatch -> Rep CreateBatch x
from :: forall x. CreateBatch -> Rep CreateBatch x
$cto :: forall x. Rep CreateBatch x -> CreateBatch
to :: forall x. Rep CreateBatch x -> CreateBatch
Generic, Int -> CreateBatch -> ShowS
[CreateBatch] -> ShowS
CreateBatch -> String
(Int -> CreateBatch -> ShowS)
-> (CreateBatch -> String)
-> ([CreateBatch] -> ShowS)
-> Show CreateBatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateBatch -> ShowS
showsPrec :: Int -> CreateBatch -> ShowS
$cshow :: CreateBatch -> String
show :: CreateBatch -> String
$cshowList :: [CreateBatch] -> ShowS
showList :: [CreateBatch] -> ShowS
Show)
deriving anyclass (Maybe CreateBatch
Value -> Parser [CreateBatch]
Value -> Parser CreateBatch
(Value -> Parser CreateBatch)
-> (Value -> Parser [CreateBatch])
-> Maybe CreateBatch
-> FromJSON CreateBatch
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CreateBatch
parseJSON :: Value -> Parser CreateBatch
$cparseJSONList :: Value -> Parser [CreateBatch]
parseJSONList :: Value -> Parser [CreateBatch]
$comittedField :: Maybe CreateBatch
omittedField :: Maybe CreateBatch
FromJSON, [CreateBatch] -> Value
[CreateBatch] -> Encoding
CreateBatch -> Bool
CreateBatch -> Value
CreateBatch -> Encoding
(CreateBatch -> Value)
-> (CreateBatch -> Encoding)
-> ([CreateBatch] -> Value)
-> ([CreateBatch] -> Encoding)
-> (CreateBatch -> Bool)
-> ToJSON CreateBatch
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CreateBatch -> Value
toJSON :: CreateBatch -> Value
$ctoEncoding :: CreateBatch -> Encoding
toEncoding :: CreateBatch -> Encoding
$ctoJSONList :: [CreateBatch] -> Value
toJSONList :: [CreateBatch] -> Value
$ctoEncodingList :: [CreateBatch] -> Encoding
toEncodingList :: [CreateBatch] -> Encoding
$comitField :: CreateBatch -> Bool
omitField :: CreateBatch -> Bool
ToJSON)
_CreateBatch :: CreateBatch
_CreateBatch :: CreateBatch
_CreateBatch = CreateBatch
{ requests :: Vector BatchRequest
requests = Vector BatchRequest
forall a. Monoid a => a
mempty
}
data ProcessingStatus
= In_Progress
| Canceling
| Ended
deriving stock (ProcessingStatus -> ProcessingStatus -> Bool
(ProcessingStatus -> ProcessingStatus -> Bool)
-> (ProcessingStatus -> ProcessingStatus -> Bool)
-> Eq ProcessingStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProcessingStatus -> ProcessingStatus -> Bool
== :: ProcessingStatus -> ProcessingStatus -> Bool
$c/= :: ProcessingStatus -> ProcessingStatus -> Bool
/= :: ProcessingStatus -> ProcessingStatus -> Bool
Eq, (forall x. ProcessingStatus -> Rep ProcessingStatus x)
-> (forall x. Rep ProcessingStatus x -> ProcessingStatus)
-> Generic ProcessingStatus
forall x. Rep ProcessingStatus x -> ProcessingStatus
forall x. ProcessingStatus -> Rep ProcessingStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProcessingStatus -> Rep ProcessingStatus x
from :: forall x. ProcessingStatus -> Rep ProcessingStatus x
$cto :: forall x. Rep ProcessingStatus x -> ProcessingStatus
to :: forall x. Rep ProcessingStatus x -> ProcessingStatus
Generic, Int -> ProcessingStatus -> ShowS
[ProcessingStatus] -> ShowS
ProcessingStatus -> String
(Int -> ProcessingStatus -> ShowS)
-> (ProcessingStatus -> String)
-> ([ProcessingStatus] -> ShowS)
-> Show ProcessingStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProcessingStatus -> ShowS
showsPrec :: Int -> ProcessingStatus -> ShowS
$cshow :: ProcessingStatus -> String
show :: ProcessingStatus -> String
$cshowList :: [ProcessingStatus] -> ShowS
showList :: [ProcessingStatus] -> ShowS
Show)
processingStatusOptions :: Options
processingStatusOptions :: Options
processingStatusOptions = Options
Aeson.defaultOptions
{ constructorTagModifier = map Char.toLower
}
instance FromJSON ProcessingStatus where
parseJSON :: Value -> Parser ProcessingStatus
parseJSON = Options -> Value -> Parser ProcessingStatus
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
processingStatusOptions
instance ToJSON ProcessingStatus where
toJSON :: ProcessingStatus -> Value
toJSON = Options -> ProcessingStatus -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
processingStatusOptions
data RequestCounts = RequestCounts
{ RequestCounts -> Natural
processing :: Natural
, RequestCounts -> Natural
succeeded :: Natural
, RequestCounts -> Natural
errored :: Natural
, RequestCounts -> Natural
canceled :: Natural
, RequestCounts -> Natural
expired :: Natural
} deriving stock ((forall x. RequestCounts -> Rep RequestCounts x)
-> (forall x. Rep RequestCounts x -> RequestCounts)
-> Generic RequestCounts
forall x. Rep RequestCounts x -> RequestCounts
forall x. RequestCounts -> Rep RequestCounts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestCounts -> Rep RequestCounts x
from :: forall x. RequestCounts -> Rep RequestCounts x
$cto :: forall x. Rep RequestCounts x -> RequestCounts
to :: forall x. Rep RequestCounts x -> RequestCounts
Generic, Int -> RequestCounts -> ShowS
[RequestCounts] -> ShowS
RequestCounts -> String
(Int -> RequestCounts -> ShowS)
-> (RequestCounts -> String)
-> ([RequestCounts] -> ShowS)
-> Show RequestCounts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestCounts -> ShowS
showsPrec :: Int -> RequestCounts -> ShowS
$cshow :: RequestCounts -> String
show :: RequestCounts -> String
$cshowList :: [RequestCounts] -> ShowS
showList :: [RequestCounts] -> ShowS
Show)
deriving anyclass (Maybe RequestCounts
Value -> Parser [RequestCounts]
Value -> Parser RequestCounts
(Value -> Parser RequestCounts)
-> (Value -> Parser [RequestCounts])
-> Maybe RequestCounts
-> FromJSON RequestCounts
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser RequestCounts
parseJSON :: Value -> Parser RequestCounts
$cparseJSONList :: Value -> Parser [RequestCounts]
parseJSONList :: Value -> Parser [RequestCounts]
$comittedField :: Maybe RequestCounts
omittedField :: Maybe RequestCounts
FromJSON, [RequestCounts] -> Value
[RequestCounts] -> Encoding
RequestCounts -> Bool
RequestCounts -> Value
RequestCounts -> Encoding
(RequestCounts -> Value)
-> (RequestCounts -> Encoding)
-> ([RequestCounts] -> Value)
-> ([RequestCounts] -> Encoding)
-> (RequestCounts -> Bool)
-> ToJSON RequestCounts
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: RequestCounts -> Value
toJSON :: RequestCounts -> Value
$ctoEncoding :: RequestCounts -> Encoding
toEncoding :: RequestCounts -> Encoding
$ctoJSONList :: [RequestCounts] -> Value
toJSONList :: [RequestCounts] -> Value
$ctoEncodingList :: [RequestCounts] -> Encoding
toEncodingList :: [RequestCounts] -> Encoding
$comitField :: RequestCounts -> Bool
omitField :: RequestCounts -> Bool
ToJSON)
data BatchObject = BatchObject
{ BatchObject -> Text
id :: Text
, BatchObject -> Text
type_ :: Text
, BatchObject -> ProcessingStatus
processing_status :: ProcessingStatus
, BatchObject -> RequestCounts
request_counts :: RequestCounts
, BatchObject -> Maybe POSIXTime
ended_at :: Maybe POSIXTime
, BatchObject -> POSIXTime
created_at :: POSIXTime
, BatchObject -> POSIXTime
expires_at :: POSIXTime
, BatchObject -> Maybe POSIXTime
cancel_initiated_at :: Maybe POSIXTime
, BatchObject -> Maybe Text
results_url :: Maybe Text
} deriving stock ((forall x. BatchObject -> Rep BatchObject x)
-> (forall x. Rep BatchObject x -> BatchObject)
-> Generic BatchObject
forall x. Rep BatchObject x -> BatchObject
forall x. BatchObject -> Rep BatchObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BatchObject -> Rep BatchObject x
from :: forall x. BatchObject -> Rep BatchObject x
$cto :: forall x. Rep BatchObject x -> BatchObject
to :: forall x. Rep BatchObject x -> BatchObject
Generic, Int -> BatchObject -> ShowS
[BatchObject] -> ShowS
BatchObject -> String
(Int -> BatchObject -> ShowS)
-> (BatchObject -> String)
-> ([BatchObject] -> ShowS)
-> Show BatchObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BatchObject -> ShowS
showsPrec :: Int -> BatchObject -> ShowS
$cshow :: BatchObject -> String
show :: BatchObject -> String
$cshowList :: [BatchObject] -> ShowS
showList :: [BatchObject] -> ShowS
Show)
instance FromJSON BatchObject where
parseJSON :: Value -> Parser BatchObject
parseJSON = Options -> Value -> Parser BatchObject
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
instance ToJSON BatchObject where
toJSON :: BatchObject -> Value
toJSON = Options -> BatchObject -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data BatchResultType
= Succeeded { BatchResultType -> MessageResponse
message :: MessageResponse }
| Errored { BatchResultType -> Error
error :: Error.Error }
| Canceled
| Expired
deriving stock ((forall x. BatchResultType -> Rep BatchResultType x)
-> (forall x. Rep BatchResultType x -> BatchResultType)
-> Generic BatchResultType
forall x. Rep BatchResultType x -> BatchResultType
forall x. BatchResultType -> Rep BatchResultType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BatchResultType -> Rep BatchResultType x
from :: forall x. BatchResultType -> Rep BatchResultType x
$cto :: forall x. Rep BatchResultType x -> BatchResultType
to :: forall x. Rep BatchResultType x -> BatchResultType
Generic, Int -> BatchResultType -> ShowS
[BatchResultType] -> ShowS
BatchResultType -> String
(Int -> BatchResultType -> ShowS)
-> (BatchResultType -> String)
-> ([BatchResultType] -> ShowS)
-> Show BatchResultType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BatchResultType -> ShowS
showsPrec :: Int -> BatchResultType -> ShowS
$cshow :: BatchResultType -> String
show :: BatchResultType -> String
$cshowList :: [BatchResultType] -> ShowS
showList :: [BatchResultType] -> ShowS
Show)
batchResultTypeOptions :: Options
batchResultTypeOptions :: Options
batchResultTypeOptions = Options
Aeson.defaultOptions
{ sumEncoding = TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
, constructorTagModifier = map Char.toLower
}
instance FromJSON BatchResultType where
parseJSON :: Value -> Parser BatchResultType
parseJSON = Options -> Value -> Parser BatchResultType
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
batchResultTypeOptions
instance ToJSON BatchResultType where
toJSON :: BatchResultType -> Value
toJSON = Options -> BatchResultType -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
batchResultTypeOptions
data BatchResult = BatchResult
{ BatchResult -> Text
custom_id :: Text
, BatchResult -> BatchResultType
result :: BatchResultType
} deriving stock ((forall x. BatchResult -> Rep BatchResult x)
-> (forall x. Rep BatchResult x -> BatchResult)
-> Generic BatchResult
forall x. Rep BatchResult x -> BatchResult
forall x. BatchResult -> Rep BatchResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BatchResult -> Rep BatchResult x
from :: forall x. BatchResult -> Rep BatchResult x
$cto :: forall x. Rep BatchResult x -> BatchResult
to :: forall x. Rep BatchResult x -> BatchResult
Generic, Int -> BatchResult -> ShowS
[BatchResult] -> ShowS
BatchResult -> String
(Int -> BatchResult -> ShowS)
-> (BatchResult -> String)
-> ([BatchResult] -> ShowS)
-> Show BatchResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BatchResult -> ShowS
showsPrec :: Int -> BatchResult -> ShowS
$cshow :: BatchResult -> String
show :: BatchResult -> String
$cshowList :: [BatchResult] -> ShowS
showList :: [BatchResult] -> ShowS
Show)
deriving anyclass (Maybe BatchResult
Value -> Parser [BatchResult]
Value -> Parser BatchResult
(Value -> Parser BatchResult)
-> (Value -> Parser [BatchResult])
-> Maybe BatchResult
-> FromJSON BatchResult
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser BatchResult
parseJSON :: Value -> Parser BatchResult
$cparseJSONList :: Value -> Parser [BatchResult]
parseJSONList :: Value -> Parser [BatchResult]
$comittedField :: Maybe BatchResult
omittedField :: Maybe BatchResult
FromJSON, [BatchResult] -> Value
[BatchResult] -> Encoding
BatchResult -> Bool
BatchResult -> Value
BatchResult -> Encoding
(BatchResult -> Value)
-> (BatchResult -> Encoding)
-> ([BatchResult] -> Value)
-> ([BatchResult] -> Encoding)
-> (BatchResult -> Bool)
-> ToJSON BatchResult
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: BatchResult -> Value
toJSON :: BatchResult -> Value
$ctoEncoding :: BatchResult -> Encoding
toEncoding :: BatchResult -> Encoding
$ctoJSONList :: [BatchResult] -> Value
toJSONList :: [BatchResult] -> Value
$ctoEncodingList :: [BatchResult] -> Encoding
toEncodingList :: [BatchResult] -> Encoding
$comitField :: BatchResult -> Bool
omitField :: BatchResult -> Bool
ToJSON)
data ListBatchesResponse = ListBatchesResponse
{ ListBatchesResponse -> Vector BatchObject
data_ :: Vector BatchObject
, ListBatchesResponse -> Bool
has_more :: Bool
, ListBatchesResponse -> Maybe Text
first_id :: Maybe Text
, ListBatchesResponse -> Maybe Text
last_id :: Maybe Text
} deriving stock ((forall x. ListBatchesResponse -> Rep ListBatchesResponse x)
-> (forall x. Rep ListBatchesResponse x -> ListBatchesResponse)
-> Generic ListBatchesResponse
forall x. Rep ListBatchesResponse x -> ListBatchesResponse
forall x. ListBatchesResponse -> Rep ListBatchesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListBatchesResponse -> Rep ListBatchesResponse x
from :: forall x. ListBatchesResponse -> Rep ListBatchesResponse x
$cto :: forall x. Rep ListBatchesResponse x -> ListBatchesResponse
to :: forall x. Rep ListBatchesResponse x -> ListBatchesResponse
Generic, Int -> ListBatchesResponse -> ShowS
[ListBatchesResponse] -> ShowS
ListBatchesResponse -> String
(Int -> ListBatchesResponse -> ShowS)
-> (ListBatchesResponse -> String)
-> ([ListBatchesResponse] -> ShowS)
-> Show ListBatchesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListBatchesResponse -> ShowS
showsPrec :: Int -> ListBatchesResponse -> ShowS
$cshow :: ListBatchesResponse -> String
show :: ListBatchesResponse -> String
$cshowList :: [ListBatchesResponse] -> ShowS
showList :: [ListBatchesResponse] -> ShowS
Show)
instance FromJSON ListBatchesResponse where
parseJSON :: Value -> Parser ListBatchesResponse
parseJSON = Options -> Value -> Parser ListBatchesResponse
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
instance ToJSON ListBatchesResponse where
toJSON :: ListBatchesResponse -> Value
toJSON = Options -> ListBatchesResponse -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
type API =
"messages"
:> "batches"
:> ( ReqBody '[JSON] CreateBatch
:> Post '[JSON] BatchObject
:<|> Capture "batch_id" Text
:> Get '[JSON] BatchObject
:<|> QueryParam "limit" Natural
:> QueryParam "before_id" Text
:> QueryParam "after_id" Text
:> Get '[JSON] ListBatchesResponse
:<|> Capture "batch_id" Text
:> "cancel"
:> Post '[JSON] BatchObject
)