Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
/v1/threads/:thread_id/runs/:run_id/steps
Synopsis
- newtype StepID = StepID {}
- data RunStepObject = RunStepObject {
- id :: StepID
- object :: Text
- created_at :: POSIXTime
- assistant_id :: AssistantID
- thread_id :: ThreadID
- run_id :: RunID
- status :: Status
- step_details :: StepDetails
- last_error :: Maybe Error
- expired_at :: Maybe POSIXTime
- cancelled_at :: Maybe POSIXTime
- failed_at :: Maybe POSIXTime
- completed_at :: Maybe POSIXTime
- metadata :: Map Text Text
- usage :: Maybe (Usage CompletionTokensDetails PromptTokensDetails)
- data Status
- data Image = Image {}
- data Output
- = Output_Logs { }
- | Output_Image { }
- data CodeInterpreter = CodeInterpreter {}
- data RankingOptions = RankingOptions {
- ranker :: Text
- score_threshold :: Double
- data Content = Content {}
- data Result = Result {}
- data FileSearch = FileSearch {
- ranking_options :: RankingOptions
- results :: Vector Result
- data Function = Function {}
- data ToolCall
- = ToolCall_Code_Interpreter { }
- | ToolCall_File_Search {
- id :: Text
- file_search :: Map Text FileSearch
- | ToolCall_Function { }
- data StepDetails
- = Message_Creation { }
- | Tool_Calls {
- tool_calls :: Vector ToolCall
- type API = "threads" :> (Header' '[Required, Strict] "OpenAI-Beta" Text :> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("steps" :> (QueryParam "limit" Natural :> (QueryParam "order" Order :> (QueryParam "after" Text :> (QueryParam "before" Text :> (QueryParam "include[]" Text :> Get '[JSON] (ListOf RunStepObject)))))))))) :<|> (Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("steps" :> (Capture "step_id" StepID :> (QueryParam "include[]" Text :> Get '[JSON] RunStepObject))))))))
Main types
Step ID
Instances
FromJSON StepID Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps | |
ToJSON StepID Source # | |
IsString StepID Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps fromString :: String -> StepID # | |
Show StepID Source # | |
ToHttpApiData StepID Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps toUrlPiece :: StepID -> Text # toEncodedUrlPiece :: StepID -> Builder # toHeader :: StepID -> ByteString # toQueryParam :: StepID -> Text # toEncodedQueryParam :: StepID -> Builder # |
data RunStepObject Source #
Represents a step in execution of a run.
RunStepObject | |
|
Instances
Other types
The status of the run step
Instances
FromJSON Status Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps | |
Generic Status Source # | |
Show Status Source # | |
type Rep Status Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps type Rep Status = D1 ('MetaData "Status" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) ((C1 ('MetaCons "In_Progress" '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 "Expired" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Code Interpreter image output
An output from the Code Interpreter tool call
Instances
FromJSON Output Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps | |
Generic Output Source # | |
Show Output Source # | |
type Rep Output Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps type Rep Output = D1 ('MetaData "Output" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Output_Logs" 'PrefixI 'True) (S1 ('MetaSel ('Just "logs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Output_Image" 'PrefixI 'True) (S1 ('MetaSel ('Just "image") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Image))) |
data CodeInterpreter Source #
A Code Interpreter tool call
Instances
data RankingOptions Source #
The ranking options for the file search.
Instances
The content of the result that was found
Instances
FromJSON Content Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps | |
Generic Content Source # | |
Show Content Source # | |
type Rep Content Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps type Rep Content = D1 ('MetaData "Content" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Content" 'PrefixI 'True) (S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
Result of the file search
Instances
FromJSON Result Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps | |
Generic Result Source # | |
Show Result Source # | |
type Rep Result Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps type Rep Result = D1 ('MetaData "Result" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Result" 'PrefixI 'True) ((S1 ('MetaSel ('Just "file_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileID) :*: S1 ('MetaSel ('Just "file_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "score") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Content))))) |
data FileSearch Source #
A File Search tool call
FileSearch | |
|
Instances
FromJSON FileSearch Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps parseJSON :: Value -> Parser FileSearch # parseJSONList :: Value -> Parser [FileSearch] # | |
Generic FileSearch Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps type Rep FileSearch :: Type -> Type # from :: FileSearch -> Rep FileSearch x # to :: Rep FileSearch x -> FileSearch # | |
Show FileSearch Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps showsPrec :: Int -> FileSearch -> ShowS # show :: FileSearch -> String # showList :: [FileSearch] -> ShowS # | |
type Rep FileSearch Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps type Rep FileSearch = D1 ('MetaData "FileSearch" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "FileSearch" 'PrefixI 'True) (S1 ('MetaSel ('Just "ranking_options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RankingOptions) :*: S1 ('MetaSel ('Just "results") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Result)))) |
The definition of the function that was called
Instances
FromJSON Function Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps | |
Generic Function Source # | |
Show Function Source # | |
type Rep Function Source # | |
Defined in OpenAI.V1.Threads.Runs.Steps type Rep Function = D1 ('MetaData "Function" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Function" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "output") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) |
A tool call the run step was involved in
ToolCall_Code_Interpreter | |
ToolCall_File_Search | |
| |
ToolCall_Function | |
Instances
data StepDetails Source #
The details of the run step
Message_Creation | |
Tool_Calls | |
|
Instances
Servant
type API = "threads" :> (Header' '[Required, Strict] "OpenAI-Beta" Text :> ((Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("steps" :> (QueryParam "limit" Natural :> (QueryParam "order" Order :> (QueryParam "after" Text :> (QueryParam "before" Text :> (QueryParam "include[]" Text :> Get '[JSON] (ListOf RunStepObject)))))))))) :<|> (Capture "thread_id" ThreadID :> ("runs" :> (Capture "run_id" RunID :> ("steps" :> (Capture "step_id" StepID :> (QueryParam "include[]" Text :> Get '[JSON] RunStepObject)))))))) Source #
Servant API