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

OpenAI.V1.Threads.Runs.Steps

Description

/v1/threads/:thread_id/runs/:run_id/steps
Synopsis

Main types

data RunStepObject Source #

Represents a step in execution of a run.

Instances

Instances details
FromJSON RunStepObject Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic RunStepObject Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep RunStepObject :: Type -> Type #

Show RunStepObject Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep RunStepObject Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep RunStepObject = D1 ('MetaData "RunStepObject" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "RunStepObject" 'PrefixI 'True) (((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StepID) :*: (S1 ('MetaSel ('Just "object") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "created_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime))) :*: ((S1 ('MetaSel ('Just "assistant_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssistantID) :*: S1 ('MetaSel ('Just "thread_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ThreadID)) :*: (S1 ('MetaSel ('Just "run_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RunID) :*: S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)))) :*: (((S1 ('MetaSel ('Just "step_details") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StepDetails) :*: S1 ('MetaSel ('Just "last_error") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Error))) :*: (S1 ('MetaSel ('Just "expired_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: S1 ('MetaSel ('Just "cancelled_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)))) :*: ((S1 ('MetaSel ('Just "failed_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: S1 ('MetaSel ('Just "completed_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime))) :*: (S1 ('MetaSel ('Just "metadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Text)) :*: S1 ('MetaSel ('Just "usage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Usage CompletionTokensDetails PromptTokensDetails))))))))

Other types

data Status Source #

The status of the run step

Instances

Instances details
FromJSON Status Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic Status Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

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.Threads.Runs.Steps

type Rep Status Source # 
Instance details

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))))

data Image Source #

Code Interpreter image output

Constructors

Image 

Fields

Instances

Instances details
FromJSON Image Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic Image Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Show Image Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

type Rep Image Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep Image = D1 ('MetaData "Image" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Image" 'PrefixI 'True) (S1 ('MetaSel ('Just "file_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileID)))

data Output Source #

An output from the Code Interpreter tool call

Constructors

Output_Logs 

Fields

Output_Image 

Fields

Instances

Instances details
FromJSON Output Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic Output Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep Output :: Type -> Type #

Methods

from :: Output -> Rep Output x #

to :: Rep Output x -> Output #

Show Output Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep Output Source # 
Instance details

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

Constructors

CodeInterpreter 

Fields

Instances

Instances details
FromJSON CodeInterpreter Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic CodeInterpreter Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep CodeInterpreter :: Type -> Type #

Show CodeInterpreter Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep CodeInterpreter Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep CodeInterpreter = D1 ('MetaData "CodeInterpreter" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "CodeInterpreter" 'PrefixI 'True) (S1 ('MetaSel ('Just "input") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "outputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Output))))

data RankingOptions Source #

The ranking options for the file search.

Constructors

RankingOptions 

Instances

Instances details
FromJSON RankingOptions Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic RankingOptions Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep RankingOptions :: Type -> Type #

Show RankingOptions Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep RankingOptions Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep RankingOptions = D1 ('MetaData "RankingOptions" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "RankingOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "ranker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "score_threshold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

data Content Source #

The content of the result that was found

Constructors

Content 

Fields

Instances

Instances details
FromJSON Content Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic Content Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep Content :: Type -> Type #

Methods

from :: Content -> Rep Content x #

to :: Rep Content x -> Content #

Show Content Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep Content Source # 
Instance details

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)))

data Result Source #

Result of the file search

Constructors

Result 

Fields

Instances

Instances details
FromJSON Result Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic Result Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep Result :: Type -> Type #

Methods

from :: Result -> Rep Result x #

to :: Rep Result x -> Result #

Show Result Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep Result Source # 
Instance details

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

Constructors

FileSearch 

Instances

Instances details
FromJSON FileSearch Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic FileSearch Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep FileSearch :: Type -> Type #

Show FileSearch Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep FileSearch Source # 
Instance details

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))))

data Function Source #

The definition of the function that was called

Constructors

Function 

Fields

Instances

Instances details
FromJSON Function Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic Function Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep Function :: Type -> Type #

Methods

from :: Function -> Rep Function x #

to :: Rep Function x -> Function #

Show Function Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep Function Source # 
Instance details

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)))))

data ToolCall Source #

A tool call the run step was involved in

Instances

Instances details
FromJSON ToolCall Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic ToolCall Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep ToolCall :: Type -> Type #

Methods

from :: ToolCall -> Rep ToolCall x #

to :: Rep ToolCall x -> ToolCall #

Show ToolCall Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep ToolCall Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep ToolCall = D1 ('MetaData "ToolCall" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "ToolCall_Code_Interpreter" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "code_interpreter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CodeInterpreter)) :+: (C1 ('MetaCons "ToolCall_File_Search" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "file_search") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text FileSearch))) :+: C1 ('MetaCons "ToolCall_Function" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "function") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Function))))

data StepDetails Source #

The details of the run step

Constructors

Message_Creation 
Tool_Calls 

Fields

Instances

Instances details
FromJSON StepDetails Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Generic StepDetails Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

Associated Types

type Rep StepDetails :: Type -> Type #

Show StepDetails Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep StepDetails Source # 
Instance details

Defined in OpenAI.V1.Threads.Runs.Steps

type Rep StepDetails = D1 ('MetaData "StepDetails" "OpenAI.V1.Threads.Runs.Steps" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Message_Creation" 'PrefixI 'True) (S1 ('MetaSel ('Just "message_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageID)) :+: C1 ('MetaCons "Tool_Calls" 'PrefixI 'True) (S1 ('MetaSel ('Just "tool_calls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector ToolCall))))

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