Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
OpenAI.V1.Assistants
Contents
Description
/v1/assistants
Synopsis
- newtype AssistantID = AssistantID {}
- data CreateAssistant = CreateAssistant {
- model :: Model
- name :: Maybe Text
- description :: Maybe Text
- instructions :: Maybe Text
- tools :: Maybe (Vector Tool)
- tool_resources :: Maybe ToolResources
- metadata :: Maybe (Map Text Text)
- temperature :: Maybe Double
- top_p :: Maybe Double
- response_format :: Maybe (AutoOr ResponseFormat)
- _CreateAssistant :: CreateAssistant
- data ModifyAssistant = ModifyAssistant {
- model :: Model
- name :: Maybe Text
- description :: Maybe Text
- instructions :: Maybe Text
- tools :: Maybe (Vector Tool)
- tool_resources :: Maybe ToolResources
- metadata :: Maybe (Map Text Text)
- temperature :: Maybe Double
- top_p :: Maybe Double
- response_format :: Maybe (AutoOr ResponseFormat)
- _ModifyAssistant :: ModifyAssistant
- data AssistantObject = AssistantObject {
- id :: AssistantID
- object :: Text
- created_at :: POSIXTime
- name :: Maybe Text
- description :: Maybe Text
- model :: Model
- instructions :: Maybe Text
- tools :: Maybe (Vector Tool)
- tool_resources :: Maybe ToolResources
- metadata :: Map Text Text
- temperature :: Maybe Double
- top_p :: Maybe Double
- response_format :: AutoOr ResponseFormat
- data RankingOptions
- data FileSearch = FileSearch {}
- data Function = Function {}
- data Tool
- = Tool_Code_Interpreter
- | Tool_File_Search { }
- | Tool_Function { }
- data CodeInterpreterResources = CodeInterpreterResources {}
- data FileSearchResources = FileSearchResources {
- vector_store_ids :: Maybe (Vector FileID)
- vector_stores :: Maybe (Vector VectorStore)
- data ToolResources = ToolResources {}
- type API = Header' '[Required, Strict] "OpenAI-Beta" Text :> ("assistants" :> ((ReqBody '[JSON] CreateAssistant :> Post '[JSON] AssistantObject) :<|> ((QueryParam "limit" Natural :> (QueryParam "order" Order :> (QueryParam "after" Text :> (QueryParam "before" Text :> Get '[JSON] (ListOf AssistantObject))))) :<|> ((Capture "assistant_id" AssistantID :> Get '[JSON] AssistantObject) :<|> ((Capture "assistant_id" AssistantID :> (ReqBody '[JSON] ModifyAssistant :> Post '[JSON] AssistantObject)) :<|> (Capture "assistant_id" AssistantID :> Delete '[JSON] DeletionStatus))))))
Main types
newtype AssistantID Source #
AssistantID
Constructors
AssistantID | |
Instances
FromJSON AssistantID Source # | |
Defined in OpenAI.V1.Assistants | |
ToJSON AssistantID Source # | |
Defined in OpenAI.V1.Assistants Methods toJSON :: AssistantID -> Value # toEncoding :: AssistantID -> Encoding # toJSONList :: [AssistantID] -> Value # toEncodingList :: [AssistantID] -> Encoding # omitField :: AssistantID -> Bool # | |
IsString AssistantID Source # | |
Defined in OpenAI.V1.Assistants Methods fromString :: String -> AssistantID # | |
Show AssistantID Source # | |
Defined in OpenAI.V1.Assistants Methods showsPrec :: Int -> AssistantID -> ShowS # show :: AssistantID -> String # showList :: [AssistantID] -> ShowS # | |
ToHttpApiData AssistantID Source # | |
Defined in OpenAI.V1.Assistants Methods toUrlPiece :: AssistantID -> Text # toEncodedUrlPiece :: AssistantID -> Builder # toHeader :: AssistantID -> ByteString # toQueryParam :: AssistantID -> Text # |
data CreateAssistant Source #
Request body for /v1/assistants
Constructors
CreateAssistant | |
Fields
|
Instances
_CreateAssistant :: CreateAssistant Source #
Default CreateAssistant
data ModifyAssistant Source #
Request body for /v1/assistants/:assistant_id
Constructors
ModifyAssistant | |
Fields
|
Instances
_ModifyAssistant :: ModifyAssistant Source #
Default ModifyAssistant
data AssistantObject Source #
Represents an assistant that can call the model and use tools.
Constructors
AssistantObject | |
Fields
|
Instances
Other types
data RankingOptions Source #
The ranking options for the file search
Instances
data FileSearch Source #
Overrides for the file search tool
Constructors
FileSearch | |
Fields |
Instances
The Function tool
Constructors
Function | |
Instances
FromJSON Function Source # | |
Defined in OpenAI.V1.Tool | |
ToJSON Function Source # | |
Generic Function Source # | |
Show Function Source # | |
type Rep Function Source # | |
Defined in OpenAI.V1.Tool type Rep Function = D1 ('MetaData "Function" "OpenAI.V1.Tool" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Function" 'PrefixI 'True) ((S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value)) :*: S1 ('MetaSel ('Just "strict") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))) |
A tool enabled on the assistant
Constructors
Tool_Code_Interpreter | |
Tool_File_Search | |
Fields | |
Tool_Function | |
Instances
FromJSON Tool Source # | |
Defined in OpenAI.V1.Tool | |
ToJSON Tool Source # | |
Generic Tool Source # | |
Show Tool Source # | |
type Rep Tool Source # | |
Defined in OpenAI.V1.Tool type Rep Tool = D1 ('MetaData "Tool" "OpenAI.V1.Tool" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Tool_Code_Interpreter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Tool_File_Search" 'PrefixI 'True) (S1 ('MetaSel ('Just "file_search") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileSearch)) :+: C1 ('MetaCons "Tool_Function" 'PrefixI 'True) (S1 ('MetaSel ('Just "function") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Function)))) |
data CodeInterpreterResources Source #
Resources for the code search tool
Constructors
CodeInterpreterResources | |
Instances
data FileSearchResources Source #
Resources for the file search tool
Constructors
FileSearchResources | |
Fields
|
Instances
data ToolResources Source #
A set of resources that are used by the assistant's tools
Constructors
ToolResources | |
Instances
Servant
type API = Header' '[Required, Strict] "OpenAI-Beta" Text :> ("assistants" :> ((ReqBody '[JSON] CreateAssistant :> Post '[JSON] AssistantObject) :<|> ((QueryParam "limit" Natural :> (QueryParam "order" Order :> (QueryParam "after" Text :> (QueryParam "before" Text :> Get '[JSON] (ListOf AssistantObject))))) :<|> ((Capture "assistant_id" AssistantID :> Get '[JSON] AssistantObject) :<|> ((Capture "assistant_id" AssistantID :> (ReqBody '[JSON] ModifyAssistant :> Post '[JSON] AssistantObject)) :<|> (Capture "assistant_id" AssistantID :> Delete '[JSON] DeletionStatus)))))) Source #
Servant API