Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
OpenAI.V1.Chat.Completions
Contents
Description
/v1/chat/completions
Streaming results are not yet supported
Synopsis
- data CreateChatCompletion = CreateChatCompletion {
- messages :: Vector (Message (Vector Content))
- model :: Model
- store :: Maybe Bool
- metadata :: Maybe (Map Text Text)
- frequency_penalty :: Maybe Double
- logit_bias :: Maybe (Map Word Int)
- logprobs :: Maybe Bool
- top_logprobs :: Maybe Word
- max_completion_tokens :: Maybe Natural
- n :: Maybe Natural
- modalities :: Maybe (Vector Modality)
- prediction :: Maybe Prediction
- audio :: Maybe AudioParameters
- presence_penalty :: Maybe Double
- response_format :: Maybe ResponseFormat
- seed :: Maybe Integer
- service_tier :: Maybe (AutoOr ServiceTier)
- stop :: Maybe (Vector Text)
- temperature :: Maybe Double
- top_p :: Maybe Double
- tools :: Maybe (Vector Tool)
- tool_choice :: Maybe ToolChoice
- parallel_tool_calls :: Maybe Bool
- user :: Maybe Text
- _CreateChatCompletion :: CreateChatCompletion
- data ChatCompletionObject = ChatCompletionObject {
- id :: Text
- choices :: Vector Choice
- created :: POSIXTime
- model :: Model
- service_tier :: Maybe ServiceTier
- system_fingerprint :: Text
- object :: Text
- usage :: Usage CompletionTokensDetails PromptTokensDetails
- data Choice = Choice {}
- data Message content
- messageToContent :: Monoid content => Message content -> content
- data Content
- = Text { }
- | Image_URL { }
- | Input_Audio { }
- data InputAudio = InputAudio {
- data_ :: Text
- format :: AudioFormat
- data ImageURL = ImageURL {}
- data AudioData = AudioData {}
- data Modality
- data Prediction = Content {}
- data Voice
- data AudioFormat
- data AudioParameters = AudioParameters {
- voice :: Voice
- format :: AudioFormat
- data ResponseFormat
- data ServiceTier = Default
- data FinishReason
- data Token = Token {}
- data LogProbs = LogProbs {}
- type API = "chat" :> ("completions" :> (ReqBody '[JSON] CreateChatCompletion :> Post '[JSON] ChatCompletionObject))
Main types
data CreateChatCompletion Source #
Request body for /v1/chat/completions
Constructors
CreateChatCompletion | |
Fields
|
Instances
data ChatCompletionObject Source #
ChatCompletion body
Constructors
ChatCompletionObject | |
Fields
|
Instances
A chat completion choice
Constructors
Choice | |
Instances
FromJSON Choice Source # | |
Defined in OpenAI.V1.Chat.Completions | |
Generic Choice Source # | |
Show Choice Source # | |
type Rep Choice Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep Choice = D1 ('MetaData "Choice" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Choice" 'PrefixI 'True) ((S1 ('MetaSel ('Just "finish_reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)) :*: (S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Message Text)) :*: S1 ('MetaSel ('Just "logprobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LogProbs))))) |
A message from the conversation so far
Constructors
System | |
User | |
Assistant | |
Fields
| |
Tool | |
Fields
|
Instances
messageToContent :: Monoid content => Message content -> content Source #
Extract the message body from a Message
Normally this would just be the content
field selector, but the problem
is that the content field for the Assistant
constructor is not required
to be present, so we provide a utility function to default to extract the
content
field for all constructors, defaulting to mempty
for the special
case where the Message
is an Assistant
constructor with a missing
content
field
A content part
Constructors
Text | |
Image_URL | |
Input_Audio | |
Fields |
Instances
ToJSON Content Source # | |
IsString Content Source # | |
Defined in OpenAI.V1.Chat.Completions Methods fromString :: String -> Content # | |
Generic Content Source # | |
Show Content Source # | |
type Rep Content Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep Content = D1 ('MetaData "Content" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Text" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "Image_URL" 'PrefixI 'True) (S1 ('MetaSel ('Just "image_url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImageURL)) :+: C1 ('MetaCons "Input_Audio" 'PrefixI 'True) (S1 ('MetaSel ('Just "input_audio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputAudio)))) |
Other types
data InputAudio Source #
Audio content part
Constructors
InputAudio | |
Fields
|
Instances
ToJSON InputAudio Source # | |
Defined in OpenAI.V1.Chat.Completions Methods toJSON :: InputAudio -> Value # toEncoding :: InputAudio -> Encoding # toJSONList :: [InputAudio] -> Value # toEncodingList :: [InputAudio] -> Encoding # omitField :: InputAudio -> Bool # | |
Generic InputAudio Source # | |
Defined in OpenAI.V1.Chat.Completions Associated Types type Rep InputAudio :: Type -> Type # | |
Show InputAudio Source # | |
Defined in OpenAI.V1.Chat.Completions Methods showsPrec :: Int -> InputAudio -> ShowS # show :: InputAudio -> String # showList :: [InputAudio] -> ShowS # | |
type Rep InputAudio Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep InputAudio = D1 ('MetaData "InputAudio" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "InputAudio" 'PrefixI 'True) (S1 ('MetaSel ('Just "data_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "format") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AudioFormat))) |
Image content part
Instances
ToJSON ImageURL Source # | |
Generic ImageURL Source # | |
Show ImageURL Source # | |
type Rep ImageURL Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep ImageURL = D1 ('MetaData "ImageURL" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "ImageURL" 'PrefixI 'True) (S1 ('MetaSel ('Just "url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "detail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AutoOr Text))))) |
Data about a previous audio response from the model. Learn more
Output types that you would like the model to generate for this request
Constructors
Modality_Text | |
Modality_Audio |
data Prediction Source #
Configuration for a Predicted Output, which can greatly improve response times when large parts of the model response are known ahead of time. This is most common when you are regenerating a file with only minor changes to most of the content
Instances
ToJSON Prediction Source # | |
Defined in OpenAI.V1.Chat.Completions Methods toJSON :: Prediction -> Value # toEncoding :: Prediction -> Encoding # toJSONList :: [Prediction] -> Value # toEncodingList :: [Prediction] -> Encoding # omitField :: Prediction -> Bool # | |
Generic Prediction Source # | |
Defined in OpenAI.V1.Chat.Completions Associated Types type Rep Prediction :: Type -> Type # | |
Show Prediction Source # | |
Defined in OpenAI.V1.Chat.Completions Methods showsPrec :: Int -> Prediction -> ShowS # show :: Prediction -> String # showList :: [Prediction] -> ShowS # | |
type Rep Prediction Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep Prediction = D1 ('MetaData "Prediction" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Content" 'PrefixI 'True) (S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
The voice the model uses to respond
Instances
ToJSON Voice Source # | |
Generic Voice Source # | |
Show Voice Source # | |
type Rep Voice Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep Voice = D1 ('MetaData "Voice" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) ((C1 ('MetaCons "Ash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ballad" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Coral" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Sage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Verse" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data AudioFormat Source #
Specifies the output audio format
Instances
data AudioParameters Source #
Parameters for audio output
Constructors
AudioParameters | |
Fields
|
Instances
data ResponseFormat Source #
An object specifying the format that the model must output
Constructors
ResponseFormat_Text | |
JSON_Object | |
JSON_Schema | |
Fields |
Instances
data ServiceTier Source #
Specifies the latency tier to use for processing the request
Constructors
Default |
Instances
FromJSON ServiceTier Source # | |
Defined in OpenAI.V1.Chat.Completions | |
ToJSON ServiceTier Source # | |
Defined in OpenAI.V1.Chat.Completions Methods toJSON :: ServiceTier -> Value # toEncoding :: ServiceTier -> Encoding # toJSONList :: [ServiceTier] -> Value # toEncodingList :: [ServiceTier] -> Encoding # omitField :: ServiceTier -> Bool # | |
Generic ServiceTier Source # | |
Defined in OpenAI.V1.Chat.Completions Associated Types type Rep ServiceTier :: Type -> Type # | |
Show ServiceTier Source # | |
Defined in OpenAI.V1.Chat.Completions Methods showsPrec :: Int -> ServiceTier -> ShowS # show :: ServiceTier -> String # showList :: [ServiceTier] -> ShowS # | |
type Rep ServiceTier Source # | |
data FinishReason Source #
The reason the model stopped generating tokens
Constructors
Stop | |
Length | |
Content_Filter | |
Tool_Calls |
Instances
FromJSON FinishReason Source # | |
Defined in OpenAI.V1.Chat.Completions | |
Generic FinishReason Source # | |
Defined in OpenAI.V1.Chat.Completions Associated Types type Rep FinishReason :: Type -> Type # | |
Show FinishReason Source # | |
Defined in OpenAI.V1.Chat.Completions Methods showsPrec :: Int -> FinishReason -> ShowS # show :: FinishReason -> String # showList :: [FinishReason] -> ShowS # | |
type Rep FinishReason Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep FinishReason = D1 ('MetaData "FinishReason" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) ((C1 ('MetaCons "Stop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Length" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Content_Filter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tool_Calls" 'PrefixI 'False) (U1 :: Type -> Type))) |
Message tokens with log probability information
Constructors
Token | |
Instances
FromJSON Token Source # | |
Defined in OpenAI.V1.Chat.Completions | |
Generic Token Source # | |
Show Token Source # | |
type Rep Token Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep Token = D1 ('MetaData "Token" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Token" 'PrefixI 'True) ((S1 ('MetaSel ('Just "token") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "logprob") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Word8))) :*: S1 ('MetaSel ('Just "top_logprobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Token)))))) |
Log probability information for the choice
Instances
FromJSON LogProbs Source # | |
Defined in OpenAI.V1.Chat.Completions | |
Generic LogProbs Source # | |
Show LogProbs Source # | |
type Rep LogProbs Source # | |
Defined in OpenAI.V1.Chat.Completions type Rep LogProbs = D1 ('MetaData "LogProbs" "OpenAI.V1.Chat.Completions" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "LogProbs" 'PrefixI 'True) (S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Token))) :*: S1 ('MetaSel ('Just "refusal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Token))))) |