module OpenAI.V1.Assistants
(
AssistantID(..)
, CreateAssistant(..)
, _CreateAssistant
, ModifyAssistant(..)
, _ModifyAssistant
, AssistantObject(..)
, RankingOptions
, FileSearch(..)
, Function(..)
, Tool(..)
, CodeInterpreterResources(..)
, FileSearchResources(..)
, ToolResources(..)
, API
) where
import OpenAI.Prelude
import OpenAI.V1.AutoOr
import OpenAI.V1.DeletionStatus
import OpenAI.V1.ListOf
import OpenAI.V1.Models (Model)
import OpenAI.V1.Order
import OpenAI.V1.ResponseFormat
import OpenAI.V1.Tool
import OpenAI.V1.ToolResources
newtype AssistantID = AssistantID{ AssistantID -> Text
text :: Text }
deriving newtype (Maybe AssistantID
Value -> Parser [AssistantID]
Value -> Parser AssistantID
(Value -> Parser AssistantID)
-> (Value -> Parser [AssistantID])
-> Maybe AssistantID
-> FromJSON AssistantID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AssistantID
parseJSON :: Value -> Parser AssistantID
$cparseJSONList :: Value -> Parser [AssistantID]
parseJSONList :: Value -> Parser [AssistantID]
$comittedField :: Maybe AssistantID
omittedField :: Maybe AssistantID
FromJSON, String -> AssistantID
(String -> AssistantID) -> IsString AssistantID
forall a. (String -> a) -> IsString a
$cfromString :: String -> AssistantID
fromString :: String -> AssistantID
IsString, Int -> AssistantID -> ShowS
[AssistantID] -> ShowS
AssistantID -> String
(Int -> AssistantID -> ShowS)
-> (AssistantID -> String)
-> ([AssistantID] -> ShowS)
-> Show AssistantID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AssistantID -> ShowS
showsPrec :: Int -> AssistantID -> ShowS
$cshow :: AssistantID -> String
show :: AssistantID -> String
$cshowList :: [AssistantID] -> ShowS
showList :: [AssistantID] -> ShowS
Show, AssistantID -> Text
AssistantID -> ByteString
AssistantID -> Builder
(AssistantID -> Text)
-> (AssistantID -> Builder)
-> (AssistantID -> ByteString)
-> (AssistantID -> Text)
-> (AssistantID -> Builder)
-> ToHttpApiData AssistantID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: AssistantID -> Text
toUrlPiece :: AssistantID -> Text
$ctoEncodedUrlPiece :: AssistantID -> Builder
toEncodedUrlPiece :: AssistantID -> Builder
$ctoHeader :: AssistantID -> ByteString
toHeader :: AssistantID -> ByteString
$ctoQueryParam :: AssistantID -> Text
toQueryParam :: AssistantID -> Text
$ctoEncodedQueryParam :: AssistantID -> Builder
toEncodedQueryParam :: AssistantID -> Builder
ToHttpApiData, [AssistantID] -> Value
[AssistantID] -> Encoding
AssistantID -> Bool
AssistantID -> Value
AssistantID -> Encoding
(AssistantID -> Value)
-> (AssistantID -> Encoding)
-> ([AssistantID] -> Value)
-> ([AssistantID] -> Encoding)
-> (AssistantID -> Bool)
-> ToJSON AssistantID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AssistantID -> Value
toJSON :: AssistantID -> Value
$ctoEncoding :: AssistantID -> Encoding
toEncoding :: AssistantID -> Encoding
$ctoJSONList :: [AssistantID] -> Value
toJSONList :: [AssistantID] -> Value
$ctoEncodingList :: [AssistantID] -> Encoding
toEncodingList :: [AssistantID] -> Encoding
$comitField :: AssistantID -> Bool
omitField :: AssistantID -> Bool
ToJSON)
data CreateAssistant = CreateAssistant
{ CreateAssistant -> Model
model :: Model
, CreateAssistant -> Maybe Text
name :: Maybe Text
, CreateAssistant -> Maybe Text
description :: Maybe Text
, CreateAssistant -> Maybe Text
instructions :: Maybe Text
, CreateAssistant -> Maybe (Vector Tool)
tools :: Maybe (Vector Tool)
, CreateAssistant -> Maybe ToolResources
tool_resources :: Maybe ToolResources
, CreateAssistant -> Maybe (Map Text Text)
metadata :: Maybe (Map Text Text)
, CreateAssistant -> Maybe Double
temperature :: Maybe Double
, CreateAssistant -> Maybe Double
top_p :: Maybe Double
, CreateAssistant -> Maybe (AutoOr ResponseFormat)
response_format :: Maybe (AutoOr ResponseFormat)
} deriving stock ((forall x. CreateAssistant -> Rep CreateAssistant x)
-> (forall x. Rep CreateAssistant x -> CreateAssistant)
-> Generic CreateAssistant
forall x. Rep CreateAssistant x -> CreateAssistant
forall x. CreateAssistant -> Rep CreateAssistant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateAssistant -> Rep CreateAssistant x
from :: forall x. CreateAssistant -> Rep CreateAssistant x
$cto :: forall x. Rep CreateAssistant x -> CreateAssistant
to :: forall x. Rep CreateAssistant x -> CreateAssistant
Generic, Int -> CreateAssistant -> ShowS
[CreateAssistant] -> ShowS
CreateAssistant -> String
(Int -> CreateAssistant -> ShowS)
-> (CreateAssistant -> String)
-> ([CreateAssistant] -> ShowS)
-> Show CreateAssistant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateAssistant -> ShowS
showsPrec :: Int -> CreateAssistant -> ShowS
$cshow :: CreateAssistant -> String
show :: CreateAssistant -> String
$cshowList :: [CreateAssistant] -> ShowS
showList :: [CreateAssistant] -> ShowS
Show)
instance ToJSON CreateAssistant where
toJSON :: CreateAssistant -> Value
toJSON = Options -> CreateAssistant -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
_CreateAssistant :: CreateAssistant
_CreateAssistant :: CreateAssistant
_CreateAssistant = CreateAssistant
{ $sel:name:CreateAssistant :: Maybe Text
name = Maybe Text
forall a. Maybe a
Nothing
, $sel:description:CreateAssistant :: Maybe Text
description = Maybe Text
forall a. Maybe a
Nothing
, $sel:instructions:CreateAssistant :: Maybe Text
instructions = Maybe Text
forall a. Maybe a
Nothing
, $sel:tools:CreateAssistant :: Maybe (Vector Tool)
tools = Maybe (Vector Tool)
forall a. Maybe a
Nothing
, $sel:tool_resources:CreateAssistant :: Maybe ToolResources
tool_resources = Maybe ToolResources
forall a. Maybe a
Nothing
, $sel:metadata:CreateAssistant :: Maybe (Map Text Text)
metadata = Maybe (Map Text Text)
forall a. Maybe a
Nothing
, $sel:temperature:CreateAssistant :: Maybe Double
temperature = Maybe Double
forall a. Maybe a
Nothing
, $sel:top_p:CreateAssistant :: Maybe Double
top_p = Maybe Double
forall a. Maybe a
Nothing
, $sel:response_format:CreateAssistant :: Maybe (AutoOr ResponseFormat)
response_format = Maybe (AutoOr ResponseFormat)
forall a. Maybe a
Nothing
}
data ModifyAssistant = ModifyAssistant
{ ModifyAssistant -> Model
model :: Model
, ModifyAssistant -> Maybe Text
name :: Maybe Text
, ModifyAssistant -> Maybe Text
description :: Maybe Text
, ModifyAssistant -> Maybe Text
instructions :: Maybe Text
, ModifyAssistant -> Maybe (Vector Tool)
tools :: Maybe (Vector Tool)
, ModifyAssistant -> Maybe ToolResources
tool_resources :: Maybe ToolResources
, ModifyAssistant -> Maybe (Map Text Text)
metadata :: Maybe (Map Text Text)
, ModifyAssistant -> Maybe Double
temperature :: Maybe Double
, ModifyAssistant -> Maybe Double
top_p :: Maybe Double
, ModifyAssistant -> Maybe (AutoOr ResponseFormat)
response_format :: Maybe (AutoOr ResponseFormat)
} deriving stock ((forall x. ModifyAssistant -> Rep ModifyAssistant x)
-> (forall x. Rep ModifyAssistant x -> ModifyAssistant)
-> Generic ModifyAssistant
forall x. Rep ModifyAssistant x -> ModifyAssistant
forall x. ModifyAssistant -> Rep ModifyAssistant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ModifyAssistant -> Rep ModifyAssistant x
from :: forall x. ModifyAssistant -> Rep ModifyAssistant x
$cto :: forall x. Rep ModifyAssistant x -> ModifyAssistant
to :: forall x. Rep ModifyAssistant x -> ModifyAssistant
Generic, Int -> ModifyAssistant -> ShowS
[ModifyAssistant] -> ShowS
ModifyAssistant -> String
(Int -> ModifyAssistant -> ShowS)
-> (ModifyAssistant -> String)
-> ([ModifyAssistant] -> ShowS)
-> Show ModifyAssistant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModifyAssistant -> ShowS
showsPrec :: Int -> ModifyAssistant -> ShowS
$cshow :: ModifyAssistant -> String
show :: ModifyAssistant -> String
$cshowList :: [ModifyAssistant] -> ShowS
showList :: [ModifyAssistant] -> ShowS
Show)
instance ToJSON ModifyAssistant where
toJSON :: ModifyAssistant -> Value
toJSON = Options -> ModifyAssistant -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
_ModifyAssistant :: ModifyAssistant
_ModifyAssistant :: ModifyAssistant
_ModifyAssistant = ModifyAssistant
{ $sel:name:ModifyAssistant :: Maybe Text
name = Maybe Text
forall a. Maybe a
Nothing
, $sel:description:ModifyAssistant :: Maybe Text
description = Maybe Text
forall a. Maybe a
Nothing
, $sel:instructions:ModifyAssistant :: Maybe Text
instructions = Maybe Text
forall a. Maybe a
Nothing
, $sel:tools:ModifyAssistant :: Maybe (Vector Tool)
tools = Maybe (Vector Tool)
forall a. Maybe a
Nothing
, $sel:tool_resources:ModifyAssistant :: Maybe ToolResources
tool_resources = Maybe ToolResources
forall a. Maybe a
Nothing
, $sel:metadata:ModifyAssistant :: Maybe (Map Text Text)
metadata = Maybe (Map Text Text)
forall a. Maybe a
Nothing
, $sel:temperature:ModifyAssistant :: Maybe Double
temperature = Maybe Double
forall a. Maybe a
Nothing
, $sel:top_p:ModifyAssistant :: Maybe Double
top_p = Maybe Double
forall a. Maybe a
Nothing
, $sel:response_format:ModifyAssistant :: Maybe (AutoOr ResponseFormat)
response_format = Maybe (AutoOr ResponseFormat)
forall a. Maybe a
Nothing
}
data AssistantObject = AssistantObject
{ AssistantObject -> AssistantID
id :: AssistantID
, AssistantObject -> Text
object :: Text
, AssistantObject -> POSIXTime
created_at :: POSIXTime
, AssistantObject -> Maybe Text
name :: Maybe Text
, AssistantObject -> Maybe Text
description :: Maybe Text
, AssistantObject -> Model
model :: Model
, AssistantObject -> Maybe Text
instructions :: Maybe Text
, AssistantObject -> Maybe (Vector Tool)
tools :: Maybe (Vector Tool)
, AssistantObject -> Maybe ToolResources
tool_resources :: Maybe ToolResources
, AssistantObject -> Map Text Text
metadata :: Map Text Text
, AssistantObject -> Maybe Double
temperature :: Maybe Double
, AssistantObject -> Maybe Double
top_p :: Maybe Double
, AssistantObject -> AutoOr ResponseFormat
response_format :: AutoOr ResponseFormat
} deriving stock ((forall x. AssistantObject -> Rep AssistantObject x)
-> (forall x. Rep AssistantObject x -> AssistantObject)
-> Generic AssistantObject
forall x. Rep AssistantObject x -> AssistantObject
forall x. AssistantObject -> Rep AssistantObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssistantObject -> Rep AssistantObject x
from :: forall x. AssistantObject -> Rep AssistantObject x
$cto :: forall x. Rep AssistantObject x -> AssistantObject
to :: forall x. Rep AssistantObject x -> AssistantObject
Generic, Int -> AssistantObject -> ShowS
[AssistantObject] -> ShowS
AssistantObject -> String
(Int -> AssistantObject -> ShowS)
-> (AssistantObject -> String)
-> ([AssistantObject] -> ShowS)
-> Show AssistantObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AssistantObject -> ShowS
showsPrec :: Int -> AssistantObject -> ShowS
$cshow :: AssistantObject -> String
show :: AssistantObject -> String
$cshowList :: [AssistantObject] -> ShowS
showList :: [AssistantObject] -> ShowS
Show)
deriving anyclass (Maybe AssistantObject
Value -> Parser [AssistantObject]
Value -> Parser AssistantObject
(Value -> Parser AssistantObject)
-> (Value -> Parser [AssistantObject])
-> Maybe AssistantObject
-> FromJSON AssistantObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AssistantObject
parseJSON :: Value -> Parser AssistantObject
$cparseJSONList :: Value -> Parser [AssistantObject]
parseJSONList :: Value -> Parser [AssistantObject]
$comittedField :: Maybe AssistantObject
omittedField :: Maybe AssistantObject
FromJSON)
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
)