module OpenAI.V1.Threads.Runs.Steps
(
StepID(..)
, RunStepObject(..)
, Status(..)
, Image(..)
, Output(..)
, CodeInterpreter(..)
, RankingOptions(..)
, Content(..)
, Result(..)
, FileSearch(..)
, Function(..)
, ToolCall(..)
, StepDetails(..)
, API
) where
import OpenAI.Prelude
import OpenAI.V1.Assistants (AssistantID)
import OpenAI.V1.Error
import OpenAI.V1.Files (FileID)
import OpenAI.V1.ListOf
import OpenAI.V1.Threads.Messages (MessageID)
import OpenAI.V1.Order
import OpenAI.V1.Threads (ThreadID)
import OpenAI.V1.Threads.Runs (RunID)
import OpenAI.V1.Usage
newtype StepID = StepID{ StepID -> Text
text :: Text }
deriving newtype (Maybe StepID
Value -> Parser [StepID]
Value -> Parser StepID
(Value -> Parser StepID)
-> (Value -> Parser [StepID]) -> Maybe StepID -> FromJSON StepID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser StepID
parseJSON :: Value -> Parser StepID
$cparseJSONList :: Value -> Parser [StepID]
parseJSONList :: Value -> Parser [StepID]
$comittedField :: Maybe StepID
omittedField :: Maybe StepID
FromJSON, String -> StepID
(String -> StepID) -> IsString StepID
forall a. (String -> a) -> IsString a
$cfromString :: String -> StepID
fromString :: String -> StepID
IsString, Int -> StepID -> ShowS
[StepID] -> ShowS
StepID -> String
(Int -> StepID -> ShowS)
-> (StepID -> String) -> ([StepID] -> ShowS) -> Show StepID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepID -> ShowS
showsPrec :: Int -> StepID -> ShowS
$cshow :: StepID -> String
show :: StepID -> String
$cshowList :: [StepID] -> ShowS
showList :: [StepID] -> ShowS
Show, StepID -> Text
StepID -> ByteString
StepID -> Builder
(StepID -> Text)
-> (StepID -> Builder)
-> (StepID -> ByteString)
-> (StepID -> Text)
-> (StepID -> Builder)
-> ToHttpApiData StepID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: StepID -> Text
toUrlPiece :: StepID -> Text
$ctoEncodedUrlPiece :: StepID -> Builder
toEncodedUrlPiece :: StepID -> Builder
$ctoHeader :: StepID -> ByteString
toHeader :: StepID -> ByteString
$ctoQueryParam :: StepID -> Text
toQueryParam :: StepID -> Text
$ctoEncodedQueryParam :: StepID -> Builder
toEncodedQueryParam :: StepID -> Builder
ToHttpApiData, [StepID] -> Value
[StepID] -> Encoding
StepID -> Bool
StepID -> Value
StepID -> Encoding
(StepID -> Value)
-> (StepID -> Encoding)
-> ([StepID] -> Value)
-> ([StepID] -> Encoding)
-> (StepID -> Bool)
-> ToJSON StepID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: StepID -> Value
toJSON :: StepID -> Value
$ctoEncoding :: StepID -> Encoding
toEncoding :: StepID -> Encoding
$ctoJSONList :: [StepID] -> Value
toJSONList :: [StepID] -> Value
$ctoEncodingList :: [StepID] -> Encoding
toEncodingList :: [StepID] -> Encoding
$comitField :: StepID -> Bool
omitField :: StepID -> Bool
ToJSON)
data Status = In_Progress | Cancelled | Failed | Completed | Expired
deriving stock ((forall x. Status -> Rep Status x)
-> (forall x. Rep Status x -> Status) -> Generic Status
forall x. Rep Status x -> Status
forall x. Status -> Rep Status x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Status -> Rep Status x
from :: forall x. Status -> Rep Status x
$cto :: forall x. Rep Status x -> Status
to :: forall x. Rep Status x -> Status
Generic, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
(Int -> Status -> ShowS)
-> (Status -> String) -> ([Status] -> ShowS) -> Show Status
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Status -> ShowS
showsPrec :: Int -> Status -> ShowS
$cshow :: Status -> String
show :: Status -> String
$cshowList :: [Status] -> ShowS
showList :: [Status] -> ShowS
Show)
instance FromJSON Status where
parseJSON :: Value -> Parser Status
parseJSON = Options -> Value -> Parser Status
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
data Image = Image{ Image -> FileID
file_id :: FileID }
deriving stock ((forall x. Image -> Rep Image x)
-> (forall x. Rep Image x -> Image) -> Generic Image
forall x. Rep Image x -> Image
forall x. Image -> Rep Image x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Image -> Rep Image x
from :: forall x. Image -> Rep Image x
$cto :: forall x. Rep Image x -> Image
to :: forall x. Rep Image x -> Image
Generic, Int -> Image -> ShowS
[Image] -> ShowS
Image -> String
(Int -> Image -> ShowS)
-> (Image -> String) -> ([Image] -> ShowS) -> Show Image
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Image -> ShowS
showsPrec :: Int -> Image -> ShowS
$cshow :: Image -> String
show :: Image -> String
$cshowList :: [Image] -> ShowS
showList :: [Image] -> ShowS
Show)
deriving anyclass (Maybe Image
Value -> Parser [Image]
Value -> Parser Image
(Value -> Parser Image)
-> (Value -> Parser [Image]) -> Maybe Image -> FromJSON Image
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Image
parseJSON :: Value -> Parser Image
$cparseJSONList :: Value -> Parser [Image]
parseJSONList :: Value -> Parser [Image]
$comittedField :: Maybe Image
omittedField :: Maybe Image
FromJSON)
data Output = Output_Logs{ Output -> Text
logs :: Text } | Output_Image{ Output -> Image
image :: Image }
deriving stock ((forall x. Output -> Rep Output x)
-> (forall x. Rep Output x -> Output) -> Generic Output
forall x. Rep Output x -> Output
forall x. Output -> Rep Output x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Output -> Rep Output x
from :: forall x. Output -> Rep Output x
$cto :: forall x. Rep Output x -> Output
to :: forall x. Rep Output x -> Output
Generic, Int -> Output -> ShowS
[Output] -> ShowS
Output -> String
(Int -> Output -> ShowS)
-> (Output -> String) -> ([Output] -> ShowS) -> Show Output
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Output -> ShowS
showsPrec :: Int -> Output -> ShowS
$cshow :: Output -> String
show :: Output -> String
$cshowList :: [Output] -> ShowS
showList :: [Output] -> ShowS
Show)
instance FromJSON Output where
parseJSON :: Value -> Parser Output
parseJSON = Options -> Value -> Parser Output
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
, constructorTagModifier = stripPrefix "Output_"
}
data CodeInterpreter = CodeInterpreter
{ CodeInterpreter -> Text
input :: Text
, CodeInterpreter -> Vector Output
outputs :: Vector Output
} deriving stock ((forall x. CodeInterpreter -> Rep CodeInterpreter x)
-> (forall x. Rep CodeInterpreter x -> CodeInterpreter)
-> Generic CodeInterpreter
forall x. Rep CodeInterpreter x -> CodeInterpreter
forall x. CodeInterpreter -> Rep CodeInterpreter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CodeInterpreter -> Rep CodeInterpreter x
from :: forall x. CodeInterpreter -> Rep CodeInterpreter x
$cto :: forall x. Rep CodeInterpreter x -> CodeInterpreter
to :: forall x. Rep CodeInterpreter x -> CodeInterpreter
Generic, Int -> CodeInterpreter -> ShowS
[CodeInterpreter] -> ShowS
CodeInterpreter -> String
(Int -> CodeInterpreter -> ShowS)
-> (CodeInterpreter -> String)
-> ([CodeInterpreter] -> ShowS)
-> Show CodeInterpreter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CodeInterpreter -> ShowS
showsPrec :: Int -> CodeInterpreter -> ShowS
$cshow :: CodeInterpreter -> String
show :: CodeInterpreter -> String
$cshowList :: [CodeInterpreter] -> ShowS
showList :: [CodeInterpreter] -> ShowS
Show)
deriving anyclass (Maybe CodeInterpreter
Value -> Parser [CodeInterpreter]
Value -> Parser CodeInterpreter
(Value -> Parser CodeInterpreter)
-> (Value -> Parser [CodeInterpreter])
-> Maybe CodeInterpreter
-> FromJSON CodeInterpreter
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CodeInterpreter
parseJSON :: Value -> Parser CodeInterpreter
$cparseJSONList :: Value -> Parser [CodeInterpreter]
parseJSONList :: Value -> Parser [CodeInterpreter]
$comittedField :: Maybe CodeInterpreter
omittedField :: Maybe CodeInterpreter
FromJSON)
data RankingOptions = RankingOptions
{ RankingOptions -> Text
ranker :: Text
, RankingOptions -> Double
score_threshold :: Double
} deriving stock ((forall x. RankingOptions -> Rep RankingOptions x)
-> (forall x. Rep RankingOptions x -> RankingOptions)
-> Generic RankingOptions
forall x. Rep RankingOptions x -> RankingOptions
forall x. RankingOptions -> Rep RankingOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RankingOptions -> Rep RankingOptions x
from :: forall x. RankingOptions -> Rep RankingOptions x
$cto :: forall x. Rep RankingOptions x -> RankingOptions
to :: forall x. Rep RankingOptions x -> RankingOptions
Generic, Int -> RankingOptions -> ShowS
[RankingOptions] -> ShowS
RankingOptions -> String
(Int -> RankingOptions -> ShowS)
-> (RankingOptions -> String)
-> ([RankingOptions] -> ShowS)
-> Show RankingOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RankingOptions -> ShowS
showsPrec :: Int -> RankingOptions -> ShowS
$cshow :: RankingOptions -> String
show :: RankingOptions -> String
$cshowList :: [RankingOptions] -> ShowS
showList :: [RankingOptions] -> ShowS
Show)
deriving anyclass (Maybe RankingOptions
Value -> Parser [RankingOptions]
Value -> Parser RankingOptions
(Value -> Parser RankingOptions)
-> (Value -> Parser [RankingOptions])
-> Maybe RankingOptions
-> FromJSON RankingOptions
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser RankingOptions
parseJSON :: Value -> Parser RankingOptions
$cparseJSONList :: Value -> Parser [RankingOptions]
parseJSONList :: Value -> Parser [RankingOptions]
$comittedField :: Maybe RankingOptions
omittedField :: Maybe RankingOptions
FromJSON)
data Content = Content
{ Content -> Text
type_ :: Text
, Content -> Text
text :: Text
} deriving stock ((forall x. Content -> Rep Content x)
-> (forall x. Rep Content x -> Content) -> Generic Content
forall x. Rep Content x -> Content
forall x. Content -> Rep Content x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Content -> Rep Content x
from :: forall x. Content -> Rep Content x
$cto :: forall x. Rep Content x -> Content
to :: forall x. Rep Content x -> Content
Generic, Int -> Content -> ShowS
[Content] -> ShowS
Content -> String
(Int -> Content -> ShowS)
-> (Content -> String) -> ([Content] -> ShowS) -> Show Content
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Content -> ShowS
showsPrec :: Int -> Content -> ShowS
$cshow :: Content -> String
show :: Content -> String
$cshowList :: [Content] -> ShowS
showList :: [Content] -> ShowS
Show)
instance FromJSON Content where
parseJSON :: Value -> Parser Content
parseJSON = Options -> Value -> Parser Content
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
data Result = Result
{ Result -> FileID
file_id :: FileID
, Result -> Text
file_name :: Text
, Result -> Double
score :: Double
, Result -> Vector Content
content :: Vector Content
} deriving stock ((forall x. Result -> Rep Result x)
-> (forall x. Rep Result x -> Result) -> Generic Result
forall x. Rep Result x -> Result
forall x. Result -> Rep Result x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Result -> Rep Result x
from :: forall x. Result -> Rep Result x
$cto :: forall x. Rep Result x -> Result
to :: forall x. Rep Result x -> Result
Generic, Int -> Result -> ShowS
[Result] -> ShowS
Result -> String
(Int -> Result -> ShowS)
-> (Result -> String) -> ([Result] -> ShowS) -> Show Result
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Result -> ShowS
showsPrec :: Int -> Result -> ShowS
$cshow :: Result -> String
show :: Result -> String
$cshowList :: [Result] -> ShowS
showList :: [Result] -> ShowS
Show)
deriving anyclass (Maybe Result
Value -> Parser [Result]
Value -> Parser Result
(Value -> Parser Result)
-> (Value -> Parser [Result]) -> Maybe Result -> FromJSON Result
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Result
parseJSON :: Value -> Parser Result
$cparseJSONList :: Value -> Parser [Result]
parseJSONList :: Value -> Parser [Result]
$comittedField :: Maybe Result
omittedField :: Maybe Result
FromJSON)
data FileSearch = FileSearch
{ FileSearch -> RankingOptions
ranking_options :: RankingOptions
, FileSearch -> Vector Result
results :: Vector Result
} deriving stock ((forall x. FileSearch -> Rep FileSearch x)
-> (forall x. Rep FileSearch x -> FileSearch) -> Generic FileSearch
forall x. Rep FileSearch x -> FileSearch
forall x. FileSearch -> Rep FileSearch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FileSearch -> Rep FileSearch x
from :: forall x. FileSearch -> Rep FileSearch x
$cto :: forall x. Rep FileSearch x -> FileSearch
to :: forall x. Rep FileSearch x -> FileSearch
Generic, Int -> FileSearch -> ShowS
[FileSearch] -> ShowS
FileSearch -> String
(Int -> FileSearch -> ShowS)
-> (FileSearch -> String)
-> ([FileSearch] -> ShowS)
-> Show FileSearch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileSearch -> ShowS
showsPrec :: Int -> FileSearch -> ShowS
$cshow :: FileSearch -> String
show :: FileSearch -> String
$cshowList :: [FileSearch] -> ShowS
showList :: [FileSearch] -> ShowS
Show)
deriving anyclass (Maybe FileSearch
Value -> Parser [FileSearch]
Value -> Parser FileSearch
(Value -> Parser FileSearch)
-> (Value -> Parser [FileSearch])
-> Maybe FileSearch
-> FromJSON FileSearch
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FileSearch
parseJSON :: Value -> Parser FileSearch
$cparseJSONList :: Value -> Parser [FileSearch]
parseJSONList :: Value -> Parser [FileSearch]
$comittedField :: Maybe FileSearch
omittedField :: Maybe FileSearch
FromJSON)
data Function = Function
{ Function -> Text
name :: Text
, Function -> Text
arguments :: Text
, Function -> Maybe Text
output :: Maybe Text
} deriving ((forall x. Function -> Rep Function x)
-> (forall x. Rep Function x -> Function) -> Generic Function
forall x. Rep Function x -> Function
forall x. Function -> Rep Function x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Function -> Rep Function x
from :: forall x. Function -> Rep Function x
$cto :: forall x. Rep Function x -> Function
to :: forall x. Rep Function x -> Function
Generic, Int -> Function -> ShowS
[Function] -> ShowS
Function -> String
(Int -> Function -> ShowS)
-> (Function -> String) -> ([Function] -> ShowS) -> Show Function
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Function -> ShowS
showsPrec :: Int -> Function -> ShowS
$cshow :: Function -> String
show :: Function -> String
$cshowList :: [Function] -> ShowS
showList :: [Function] -> ShowS
Show)
deriving anyclass (Maybe Function
Value -> Parser [Function]
Value -> Parser Function
(Value -> Parser Function)
-> (Value -> Parser [Function])
-> Maybe Function
-> FromJSON Function
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Function
parseJSON :: Value -> Parser Function
$cparseJSONList :: Value -> Parser [Function]
parseJSONList :: Value -> Parser [Function]
$comittedField :: Maybe Function
omittedField :: Maybe Function
FromJSON)
data ToolCall
= ToolCall_Code_Interpreter { ToolCall -> Text
id :: Text, ToolCall -> CodeInterpreter
code_interpreter :: CodeInterpreter }
| ToolCall_File_Search { id :: Text, ToolCall -> Map Text FileSearch
file_search :: Map Text FileSearch }
| ToolCall_Function { id :: Text, ToolCall -> Function
function :: Function }
deriving stock ((forall x. ToolCall -> Rep ToolCall x)
-> (forall x. Rep ToolCall x -> ToolCall) -> Generic ToolCall
forall x. Rep ToolCall x -> ToolCall
forall x. ToolCall -> Rep ToolCall x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToolCall -> Rep ToolCall x
from :: forall x. ToolCall -> Rep ToolCall x
$cto :: forall x. Rep ToolCall x -> ToolCall
to :: forall x. Rep ToolCall x -> ToolCall
Generic, Int -> ToolCall -> ShowS
[ToolCall] -> ShowS
ToolCall -> String
(Int -> ToolCall -> ShowS)
-> (ToolCall -> String) -> ([ToolCall] -> ShowS) -> Show ToolCall
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolCall -> ShowS
showsPrec :: Int -> ToolCall -> ShowS
$cshow :: ToolCall -> String
show :: ToolCall -> String
$cshowList :: [ToolCall] -> ShowS
showList :: [ToolCall] -> ShowS
Show)
instance FromJSON ToolCall where
parseJSON :: Value -> Parser ToolCall
parseJSON = Options -> Value -> Parser ToolCall
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
, constructorTagModifier = stripPrefix "ToolCall_"
}
data StepDetails
= Message_Creation{ StepDetails -> MessageID
message_id :: MessageID }
| Tool_Calls{ StepDetails -> Vector ToolCall
tool_calls :: Vector ToolCall }
deriving stock ((forall x. StepDetails -> Rep StepDetails x)
-> (forall x. Rep StepDetails x -> StepDetails)
-> Generic StepDetails
forall x. Rep StepDetails x -> StepDetails
forall x. StepDetails -> Rep StepDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StepDetails -> Rep StepDetails x
from :: forall x. StepDetails -> Rep StepDetails x
$cto :: forall x. Rep StepDetails x -> StepDetails
to :: forall x. Rep StepDetails x -> StepDetails
Generic, Int -> StepDetails -> ShowS
[StepDetails] -> ShowS
StepDetails -> String
(Int -> StepDetails -> ShowS)
-> (StepDetails -> String)
-> ([StepDetails] -> ShowS)
-> Show StepDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepDetails -> ShowS
showsPrec :: Int -> StepDetails -> ShowS
$cshow :: StepDetails -> String
show :: StepDetails -> String
$cshowList :: [StepDetails] -> ShowS
showList :: [StepDetails] -> ShowS
Show)
instance FromJSON StepDetails where
parseJSON :: Value -> Parser StepDetails
parseJSON = Options -> Value -> Parser StepDetails
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
}
data RunStepObject = RunStepObject
{ RunStepObject -> StepID
id :: StepID
, RunStepObject -> Text
object :: Text
, RunStepObject -> POSIXTime
created_at :: POSIXTime
, RunStepObject -> AssistantID
assistant_id :: AssistantID
, RunStepObject -> ThreadID
thread_id :: ThreadID
, RunStepObject -> RunID
run_id :: RunID
, RunStepObject -> Status
status :: Status
, RunStepObject -> StepDetails
step_details :: StepDetails
, RunStepObject -> Maybe Error
last_error :: Maybe Error
, RunStepObject -> Maybe POSIXTime
expired_at :: Maybe POSIXTime
, RunStepObject -> Maybe POSIXTime
cancelled_at :: Maybe POSIXTime
, RunStepObject -> Maybe POSIXTime
failed_at :: Maybe POSIXTime
, RunStepObject -> Maybe POSIXTime
completed_at :: Maybe POSIXTime
, RunStepObject -> Map Text Text
metadata :: Map Text Text
, RunStepObject
-> Maybe (Usage CompletionTokensDetails PromptTokensDetails)
usage :: Maybe (Usage CompletionTokensDetails PromptTokensDetails)
} deriving stock ((forall x. RunStepObject -> Rep RunStepObject x)
-> (forall x. Rep RunStepObject x -> RunStepObject)
-> Generic RunStepObject
forall x. Rep RunStepObject x -> RunStepObject
forall x. RunStepObject -> Rep RunStepObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RunStepObject -> Rep RunStepObject x
from :: forall x. RunStepObject -> Rep RunStepObject x
$cto :: forall x. Rep RunStepObject x -> RunStepObject
to :: forall x. Rep RunStepObject x -> RunStepObject
Generic, Int -> RunStepObject -> ShowS
[RunStepObject] -> ShowS
RunStepObject -> String
(Int -> RunStepObject -> ShowS)
-> (RunStepObject -> String)
-> ([RunStepObject] -> ShowS)
-> Show RunStepObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RunStepObject -> ShowS
showsPrec :: Int -> RunStepObject -> ShowS
$cshow :: RunStepObject -> String
show :: RunStepObject -> String
$cshowList :: [RunStepObject] -> ShowS
showList :: [RunStepObject] -> ShowS
Show)
deriving anyclass (Maybe RunStepObject
Value -> Parser [RunStepObject]
Value -> Parser RunStepObject
(Value -> Parser RunStepObject)
-> (Value -> Parser [RunStepObject])
-> Maybe RunStepObject
-> FromJSON RunStepObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser RunStepObject
parseJSON :: Value -> Parser RunStepObject
$cparseJSONList :: Value -> Parser [RunStepObject]
parseJSONList :: Value -> Parser [RunStepObject]
$comittedField :: Maybe RunStepObject
omittedField :: Maybe RunStepObject
FromJSON)
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
)