Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
/v1/threads/:thread_id/runs
Synopsis
- newtype RunID = RunID {}
- data CreateRun = CreateRun {
- assistant_id :: AssistantID
- model :: Maybe Model
- instructions :: Maybe Text
- additional_instructions :: Maybe Text
- additional_messages :: Maybe (Vector Message)
- tools :: Maybe (Vector Tool)
- metadata :: Maybe (Map Text Text)
- temperature :: Maybe Double
- top_p :: Maybe Double
- max_prompt_tokens :: Maybe Natural
- max_completion_tokens :: Maybe Natural
- truncation_strategy :: Maybe TruncationStrategy
- tool_choice :: Maybe ToolChoice
- parallel_tool_calls :: Maybe Bool
- response_format :: Maybe (AutoOr ResponseFormat)
- _CreateRun :: CreateRun
- data CreateThreadAndRun = CreateThreadAndRun {
- assistant_id :: AssistantID
- thread :: Maybe Thread
- model :: Maybe Model
- instructions :: Maybe Text
- tools :: Maybe (Vector Tool)
- toolResources :: Maybe ToolResources
- metadata :: Maybe (Map Text Text)
- temperature :: Maybe Double
- top_p :: Maybe Double
- max_prompt_tokens :: Maybe Natural
- max_completion_tokens :: Maybe Natural
- truncation_strategy :: Maybe TruncationStrategy
- tool_choice :: Maybe ToolChoice
- parallel_tool_calls :: Maybe Bool
- response_format :: Maybe (AutoOr ResponseFormat)
- _CreateThreadAndRun :: CreateThreadAndRun
- data ModifyRun = ModifyRun {}
- _ModifyRun :: ModifyRun
- data SubmitToolOutputsToRun = SubmitToolOutputsToRun {
- tool_outputs :: Vector ToolOutput
- _SubmitToolOutputsToRun :: SubmitToolOutputsToRun
- data RunObject = RunObject {
- id :: RunID
- object :: Text
- created_at :: POSIXTime
- thread_id :: ThreadID
- assistant_id :: AssistantID
- status :: Status
- required_action :: Maybe RequiredAction
- last_error :: Maybe Error
- expires_at :: Maybe POSIXTime
- started_at :: Maybe POSIXTime
- cancelled_at :: Maybe POSIXTime
- failed_at :: Maybe POSIXTime
- completed_at :: Maybe POSIXTime
- incomplete_details :: Maybe IncompleteDetails
- model :: Model
- instructions :: Maybe Text
- tools :: Vector Tool
- metadata :: Map Text Text
- usage :: Maybe (Usage (Maybe Void) (Maybe Void))
- temperature :: Maybe Double
- top_p :: Maybe Double
- max_prompt_tokens :: Maybe Natural
- max_completion_tokens :: Maybe Natural
- truncation_strategy :: Maybe TruncationStrategy
- tool_choice :: ToolChoice
- parallel_tool_calls :: Bool
- response_format :: AutoOr ResponseFormat
- data TruncationStrategy
- = Auto
- | Last_Messages { }
- data SubmitToolOutputs = SubmitToolOutputs {
- tool_calls :: Vector ToolCall
- data RequiredAction = RequiredAction_Submit_Tool_Outputs {}
- data IncompleteDetails = IncompleteDetails {}
- data ToolOutput = ToolOutput {
- tool_call_id :: Maybe Text
- output :: Text
- data Status
- type API = "threads" :> (Header' '[Required, Strict] "OpenAI-Beta" Text :> ((Capture "thread_id" ThreadID :> ("runs" :> (QueryParam "include[]" Text :> (ReqBody '[JSON] CreateRun :> Post '[JSON] RunObject)))) :<|> (("runs" :> (ReqBody '[JSON] CreateThreadAndRun :> Post '[JSON] RunObject)) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (QueryParam "limit" Natural :> (QueryParam "order" Order :> (QueryParam "after" Text :> (QueryParam "before" Text :> Get '[JSON] (ListOf RunObject))))))) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> Get '[JSON] RunObject))) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> (ReqBody '[JSON] ModifyRun :> Post '[JSON] RunObject)))) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("submit_tool_outputs" :> (ReqBody '[JSON] SubmitToolOutputsToRun :> Post '[JSON] RunObject))))) :<|> (Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("cancel" :> Post '[JSON] RunObject)))))))))))
Main types
Run ID
Instances
FromJSON RunID Source # | |
Defined in OpenAI.V1.Threads.Runs | |
ToJSON RunID Source # | |
IsString RunID Source # | |
Defined in OpenAI.V1.Threads.Runs fromString :: String -> RunID # | |
Show RunID Source # | |
ToHttpApiData RunID Source # | |
Defined in OpenAI.V1.Threads.Runs toUrlPiece :: RunID -> Text # toEncodedUrlPiece :: RunID -> Builder # toHeader :: RunID -> ByteString # toQueryParam :: RunID -> Text # toEncodedQueryParam :: RunID -> Builder # |
Request body for /v1/threads/:thread_id/runs
CreateRun | |
|
Instances
_CreateRun :: CreateRun Source #
Default CreateRun
data CreateThreadAndRun Source #
Request body for /v1/threads/runs
CreateThreadAndRun | |
|
Instances
Request body for /v1/threads/:thread_id/runs/:run_id
_ModifyRun :: ModifyRun Source #
Default ModifyRun
data SubmitToolOutputsToRun Source #
Request body for /v1/threads/:thread_id/runs/:run_id/submit_tool_outputs
SubmitToolOutputsToRun | |
|
Instances
_SubmitToolOutputsToRun :: SubmitToolOutputsToRun Source #
Default implementation of SubmitToolOutputsToRun
Represents an execution run on a thread.
RunObject | |
|
Instances
Other types
data TruncationStrategy Source #
Controls for how a thread will be truncated prior to the run
Instances
data SubmitToolOutputs Source #
Details on the tool outputs needed for this run to continue.
SubmitToolOutputs | |
|
Instances
FromJSON SubmitToolOutputs Source # | |
Defined in OpenAI.V1.Threads.Runs | |
Generic SubmitToolOutputs Source # | |
Defined in OpenAI.V1.Threads.Runs type Rep SubmitToolOutputs :: Type -> Type # from :: SubmitToolOutputs -> Rep SubmitToolOutputs x # to :: Rep SubmitToolOutputs x -> SubmitToolOutputs # | |
Show SubmitToolOutputs Source # | |
Defined in OpenAI.V1.Threads.Runs showsPrec :: Int -> SubmitToolOutputs -> ShowS # show :: SubmitToolOutputs -> String # showList :: [SubmitToolOutputs] -> ShowS # | |
type Rep SubmitToolOutputs Source # | |
Defined in OpenAI.V1.Threads.Runs type Rep SubmitToolOutputs = D1 ('MetaData "SubmitToolOutputs" "OpenAI.V1.Threads.Runs" "openai-1.0.1-3DuKyEdOLg0ITkiRYLcBus" 'False) (C1 ('MetaCons "SubmitToolOutputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "tool_calls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector ToolCall)))) |
data RequiredAction Source #
Details on the action required to continue the run
Instances
FromJSON RequiredAction Source # | |
Defined in OpenAI.V1.Threads.Runs parseJSON :: Value -> Parser RequiredAction # parseJSONList :: Value -> Parser [RequiredAction] # | |
Generic RequiredAction Source # | |
Defined in OpenAI.V1.Threads.Runs type Rep RequiredAction :: Type -> Type # from :: RequiredAction -> Rep RequiredAction x # to :: Rep RequiredAction x -> RequiredAction # | |
Show RequiredAction Source # | |
Defined in OpenAI.V1.Threads.Runs showsPrec :: Int -> RequiredAction -> ShowS # show :: RequiredAction -> String # showList :: [RequiredAction] -> ShowS # | |
type Rep RequiredAction Source # | |
Defined in OpenAI.V1.Threads.Runs type Rep RequiredAction = D1 ('MetaData "RequiredAction" "OpenAI.V1.Threads.Runs" "openai-1.0.1-3DuKyEdOLg0ITkiRYLcBus" 'False) (C1 ('MetaCons "RequiredAction_Submit_Tool_Outputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "submit_tool_outputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubmitToolOutputs))) |
data IncompleteDetails Source #
Details on why the run is incomplete
Instances
FromJSON IncompleteDetails Source # | |
Defined in OpenAI.V1.Threads.Runs | |
Generic IncompleteDetails Source # | |
Defined in OpenAI.V1.Threads.Runs type Rep IncompleteDetails :: Type -> Type # from :: IncompleteDetails -> Rep IncompleteDetails x # to :: Rep IncompleteDetails x -> IncompleteDetails # | |
Show IncompleteDetails Source # | |
Defined in OpenAI.V1.Threads.Runs showsPrec :: Int -> IncompleteDetails -> ShowS # show :: IncompleteDetails -> String # showList :: [IncompleteDetails] -> ShowS # | |
type Rep IncompleteDetails Source # | |
Defined in OpenAI.V1.Threads.Runs type Rep IncompleteDetails = D1 ('MetaData "IncompleteDetails" "OpenAI.V1.Threads.Runs" "openai-1.0.1-3DuKyEdOLg0ITkiRYLcBus" 'False) (C1 ('MetaCons "IncompleteDetails" 'PrefixI 'True) (S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
data ToolOutput Source #
A tool for which the output is being submitted
ToolOutput | |
|
Instances
The status of the run
Instances
FromJSON Status Source # | |
Defined in OpenAI.V1.Threads.Runs | |
Generic Status Source # | |
Show Status Source # | |
type Rep Status Source # | |
Defined in OpenAI.V1.Threads.Runs type Rep Status = D1 ('MetaData "Status" "OpenAI.V1.Threads.Runs" "openai-1.0.1-3DuKyEdOLg0ITkiRYLcBus" 'False) (((C1 ('MetaCons "Queued" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "In_Progress" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Requires_Action" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cancelling" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Cancelled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Failed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Completed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Incomplete" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Expired" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Servant
type API = "threads" :> (Header' '[Required, Strict] "OpenAI-Beta" Text :> ((Capture "thread_id" ThreadID :> ("runs" :> (QueryParam "include[]" Text :> (ReqBody '[JSON] CreateRun :> Post '[JSON] RunObject)))) :<|> (("runs" :> (ReqBody '[JSON] CreateThreadAndRun :> Post '[JSON] RunObject)) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (QueryParam "limit" Natural :> (QueryParam "order" Order :> (QueryParam "after" Text :> (QueryParam "before" Text :> Get '[JSON] (ListOf RunObject))))))) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> Get '[JSON] RunObject))) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> (ReqBody '[JSON] ModifyRun :> Post '[JSON] RunObject)))) :<|> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("submit_tool_outputs" :> (ReqBody '[JSON] SubmitToolOutputsToRun :> Post '[JSON] RunObject))))) :<|> (Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("cancel" :> Post '[JSON] RunObject))))))))))) Source #
Servant API