openai-1.0.0: Servant bindings to OpenAI
Safe HaskellSafe-Inferred
LanguageHaskell2010

OpenAI.V1.Batches

Description

/v1/batches
Synopsis

Main types

newtype BatchID Source #

Batch ID

Constructors

BatchID 

Fields

data CreateBatch Source #

Request body for /v1/batches

Instances

Instances details
ToJSON CreateBatch Source # 
Instance details

Defined in OpenAI.V1.Batches

Generic CreateBatch Source # 
Instance details

Defined in OpenAI.V1.Batches

Associated Types

type Rep CreateBatch :: Type -> Type #

Show CreateBatch Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep CreateBatch Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep CreateBatch = D1 ('MetaData "CreateBatch" "OpenAI.V1.Batches" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "CreateBatch" 'PrefixI 'True) ((S1 ('MetaSel ('Just "input_file_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileID) :*: S1 ('MetaSel ('Just "endpoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "completion_window") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "metadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Text))))))

data BatchObject Source #

The batch object

Instances

Instances details
FromJSON BatchObject Source # 
Instance details

Defined in OpenAI.V1.Batches

Generic BatchObject Source # 
Instance details

Defined in OpenAI.V1.Batches

Associated Types

type Rep BatchObject :: Type -> Type #

Show BatchObject Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep BatchObject Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep BatchObject = D1 ('MetaData "BatchObject" "OpenAI.V1.Batches" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "BatchObject" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BatchID) :*: S1 ('MetaSel ('Just "object") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "endpoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "errors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ListOf Error))) :*: S1 ('MetaSel ('Just "input_file_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileID)))) :*: ((S1 ('MetaSel ('Just "completion_window") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)) :*: (S1 ('MetaSel ('Just "output_file_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FileID)) :*: (S1 ('MetaSel ('Just "error_file_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FileID)) :*: S1 ('MetaSel ('Just "created_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime))))) :*: (((S1 ('MetaSel ('Just "in_progress_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: S1 ('MetaSel ('Just "expires_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime))) :*: (S1 ('MetaSel ('Just "finalizing_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: (S1 ('MetaSel ('Just "completed_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: S1 ('MetaSel ('Just "failed_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime))))) :*: ((S1 ('MetaSel ('Just "expired_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: S1 ('MetaSel ('Just "cancelling_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime))) :*: (S1 ('MetaSel ('Just "cancelled_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: (S1 ('MetaSel ('Just "request_counts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Counts)) :*: S1 ('MetaSel ('Just "metadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Text)))))))))

Other types

data Status Source #

The current status of the batch.

Instances

Instances details
FromJSON Status Source # 
Instance details

Defined in OpenAI.V1.Batches

Generic Status Source # 
Instance details

Defined in OpenAI.V1.Batches

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

Show Status Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep Status Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep Status = D1 ('MetaData "Status" "OpenAI.V1.Batches" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (((C1 ('MetaCons "Validating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Failed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "In_Progress" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Finalizing" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Completed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Expired" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Cancelling" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cancelled" 'PrefixI 'False) (U1 :: Type -> Type))))

data Counts Source #

The request counts for different statuses within the batch.

Constructors

Counts 

Instances

Instances details
FromJSON Counts Source # 
Instance details

Defined in OpenAI.V1.Batches

Generic Counts Source # 
Instance details

Defined in OpenAI.V1.Batches

Associated Types

type Rep Counts :: Type -> Type #

Methods

from :: Counts -> Rep Counts x #

to :: Rep Counts x -> Counts #

Show Counts Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep Counts Source # 
Instance details

Defined in OpenAI.V1.Batches

type Rep Counts = D1 ('MetaData "Counts" "OpenAI.V1.Batches" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Counts" 'PrefixI 'True) (S1 ('MetaSel ('Just "total") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: (S1 ('MetaSel ('Just "completed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "failed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural))))

Servant

type API = "batches" :> ((ReqBody '[JSON] CreateBatch :> Post '[JSON] BatchObject) :<|> ((Capture "batch_id" BatchID :> Get '[JSON] BatchObject) :<|> ((Capture "batch_id" BatchID :> ("cancel" :> Post '[JSON] BatchObject)) :<|> (QueryParam "after" Text :> (QueryParam "limit" Natural :> Get '[JSON] (ListOf BatchObject)))))) Source #

Servant API