{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC
-fno-warn-unused-binds -fno-warn-unused-imports -freduction-depth=328 #-}
module OpenAI.API
(
Config(..)
, OpenAIBackend(..)
, createOpenAIClient
, runOpenAIServer
, runOpenAIMiddlewareServer
, runOpenAIClient
, runOpenAIClientWithManager
, callOpenAI
, OpenAIClient
, OpenAIClientError(..)
, OpenAIAPI
, serverWaiApplicationOpenAI
, OpenAIAuth(..)
, clientAuth
, Protected
) where
import OpenAI.Types
import Control.Monad.Catch (Exception, MonadThrow, throwM)
import Control.Monad.Except (ExceptT, runExceptT)
import Control.Monad.IO.Class
import Control.Monad.Trans.Reader (ReaderT (..))
import Data.Aeson (Value)
import Data.ByteString (ByteString, fromStrict, toStrict)
import Data.Coerce (coerce)
import Data.Data (Data)
import Data.Function ((&))
import qualified Data.Map as Map
import Data.Monoid ((<>))
import Data.Proxy (Proxy (..))
import Data.Set (Set)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time
import Data.UUID (UUID)
import GHC.Exts (IsString (..))
import GHC.Generics (Generic)
import Network.HTTP.Client (Manager, newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Network.HTTP.Types.Method (methodOptions)
import Network.Wai (Middleware, Request, requestHeaders)
import qualified Network.Wai.Handler.Warp as Warp
import Network.Wai.Middleware.HttpAuth (extractBearerAuth)
import Servant (ServerError, serveWithContextT, throwError)
import Servant.API hiding (addHeader)
import Servant.API.Verbs (StdMethod (..), Verb)
import Servant.API.Experimental.Auth (AuthProtect)
import Servant.Client (ClientEnv, Scheme (Http), ClientError, client,
mkClientEnv, parseBaseUrl)
import Servant.Client.Core (baseUrlPort, baseUrlHost, AuthClientData, AuthenticatedRequest, addHeader, mkAuthenticatedRequest)
import Servant.Client.Internal.HttpClient (ClientM (..))
import Servant.Server (Handler (..), Application, Context ((:.), EmptyContext))
import Servant.Server.Experimental.Auth (AuthHandler, AuthServerData, mkAuthHandler)
import Servant.Server.StaticFiles (serveDirectoryFileServer)
import Web.FormUrlEncoded
import Web.HttpApiData
import qualified Network.HTTP.Media as M
import Data.Data
data FormCreateTranscription = FormCreateTranscription
{ FormCreateTranscription -> FilePath
createTranscriptionFile :: FilePath
, FormCreateTranscription -> FilePath
createTranslationModel :: String
, FormCreateTranscription -> Text
createTranscriptionLanguage :: Text
, FormCreateTranscription -> Text
createTranscriptionPrompt :: Text
, FormCreateTranscription -> Text
createTranscriptionResponseFormat :: Text
, FormCreateTranscription -> Double
createTranscriptionTemperature :: Double
, FormCreateTranscription -> [Text]
createTranscriptionTimestampGranularities :: [Text]
} deriving (Int -> FormCreateTranscription -> ShowS
[FormCreateTranscription] -> ShowS
FormCreateTranscription -> FilePath
(Int -> FormCreateTranscription -> ShowS)
-> (FormCreateTranscription -> FilePath)
-> ([FormCreateTranscription] -> ShowS)
-> Show FormCreateTranscription
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormCreateTranscription -> ShowS
showsPrec :: Int -> FormCreateTranscription -> ShowS
$cshow :: FormCreateTranscription -> FilePath
show :: FormCreateTranscription -> FilePath
$cshowList :: [FormCreateTranscription] -> ShowS
showList :: [FormCreateTranscription] -> ShowS
Show, FormCreateTranscription -> FormCreateTranscription -> Bool
(FormCreateTranscription -> FormCreateTranscription -> Bool)
-> (FormCreateTranscription -> FormCreateTranscription -> Bool)
-> Eq FormCreateTranscription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormCreateTranscription -> FormCreateTranscription -> Bool
== :: FormCreateTranscription -> FormCreateTranscription -> Bool
$c/= :: FormCreateTranscription -> FormCreateTranscription -> Bool
/= :: FormCreateTranscription -> FormCreateTranscription -> Bool
Eq, (forall x.
FormCreateTranscription -> Rep FormCreateTranscription x)
-> (forall x.
Rep FormCreateTranscription x -> FormCreateTranscription)
-> Generic FormCreateTranscription
forall x. Rep FormCreateTranscription x -> FormCreateTranscription
forall x. FormCreateTranscription -> Rep FormCreateTranscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FormCreateTranscription -> Rep FormCreateTranscription x
from :: forall x. FormCreateTranscription -> Rep FormCreateTranscription x
$cto :: forall x. Rep FormCreateTranscription x -> FormCreateTranscription
to :: forall x. Rep FormCreateTranscription x -> FormCreateTranscription
Generic, Typeable FormCreateTranscription
Typeable FormCreateTranscription =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranscription
-> c FormCreateTranscription)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranscription)
-> (FormCreateTranscription -> Constr)
-> (FormCreateTranscription -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranscription))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranscription))
-> ((forall b. Data b => b -> b)
-> FormCreateTranscription -> FormCreateTranscription)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> FormCreateTranscription -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> FormCreateTranscription -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription)
-> Data FormCreateTranscription
FormCreateTranscription -> Constr
FormCreateTranscription -> DataType
(forall b. Data b => b -> b)
-> FormCreateTranscription -> FormCreateTranscription
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateTranscription -> u
forall u.
(forall d. Data d => d -> u) -> FormCreateTranscription -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranscription
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranscription
-> c FormCreateTranscription
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranscription)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranscription)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranscription
-> c FormCreateTranscription
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranscription
-> c FormCreateTranscription
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranscription
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranscription
$ctoConstr :: FormCreateTranscription -> Constr
toConstr :: FormCreateTranscription -> Constr
$cdataTypeOf :: FormCreateTranscription -> DataType
dataTypeOf :: FormCreateTranscription -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranscription)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranscription)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranscription)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranscription)
$cgmapT :: (forall b. Data b => b -> b)
-> FormCreateTranscription -> FormCreateTranscription
gmapT :: (forall b. Data b => b -> b)
-> FormCreateTranscription -> FormCreateTranscription
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranscription
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateTranscription -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateTranscription -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateTranscription -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateTranscription -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranscription -> m FormCreateTranscription
Data)
instance FromForm FormCreateTranscription
instance ToForm FormCreateTranscription
data FormCreateTranslation = FormCreateTranslation
{ FormCreateTranslation -> FilePath
createTranslationFile :: FilePath
, FormCreateTranslation -> FilePath
createTranslationModel :: String
, FormCreateTranslation -> Text
createTranslationPrompt :: Text
, FormCreateTranslation -> Text
createTranslationResponseFormat :: Text
, FormCreateTranslation -> Double
createTranslationTemperature :: Double
} deriving (Int -> FormCreateTranslation -> ShowS
[FormCreateTranslation] -> ShowS
FormCreateTranslation -> FilePath
(Int -> FormCreateTranslation -> ShowS)
-> (FormCreateTranslation -> FilePath)
-> ([FormCreateTranslation] -> ShowS)
-> Show FormCreateTranslation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormCreateTranslation -> ShowS
showsPrec :: Int -> FormCreateTranslation -> ShowS
$cshow :: FormCreateTranslation -> FilePath
show :: FormCreateTranslation -> FilePath
$cshowList :: [FormCreateTranslation] -> ShowS
showList :: [FormCreateTranslation] -> ShowS
Show, FormCreateTranslation -> FormCreateTranslation -> Bool
(FormCreateTranslation -> FormCreateTranslation -> Bool)
-> (FormCreateTranslation -> FormCreateTranslation -> Bool)
-> Eq FormCreateTranslation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormCreateTranslation -> FormCreateTranslation -> Bool
== :: FormCreateTranslation -> FormCreateTranslation -> Bool
$c/= :: FormCreateTranslation -> FormCreateTranslation -> Bool
/= :: FormCreateTranslation -> FormCreateTranslation -> Bool
Eq, (forall x. FormCreateTranslation -> Rep FormCreateTranslation x)
-> (forall x. Rep FormCreateTranslation x -> FormCreateTranslation)
-> Generic FormCreateTranslation
forall x. Rep FormCreateTranslation x -> FormCreateTranslation
forall x. FormCreateTranslation -> Rep FormCreateTranslation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FormCreateTranslation -> Rep FormCreateTranslation x
from :: forall x. FormCreateTranslation -> Rep FormCreateTranslation x
$cto :: forall x. Rep FormCreateTranslation x -> FormCreateTranslation
to :: forall x. Rep FormCreateTranslation x -> FormCreateTranslation
Generic, Typeable FormCreateTranslation
Typeable FormCreateTranslation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranslation
-> c FormCreateTranslation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranslation)
-> (FormCreateTranslation -> Constr)
-> (FormCreateTranslation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranslation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranslation))
-> ((forall b. Data b => b -> b)
-> FormCreateTranslation -> FormCreateTranslation)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranslation
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateTranslation
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> FormCreateTranslation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateTranslation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation)
-> Data FormCreateTranslation
FormCreateTranslation -> Constr
FormCreateTranslation -> DataType
(forall b. Data b => b -> b)
-> FormCreateTranslation -> FormCreateTranslation
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateTranslation -> u
forall u.
(forall d. Data d => d -> u) -> FormCreateTranslation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateTranslation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateTranslation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranslation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranslation
-> c FormCreateTranslation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranslation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranslation)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranslation
-> c FormCreateTranslation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateTranslation
-> c FormCreateTranslation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranslation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateTranslation
$ctoConstr :: FormCreateTranslation -> Constr
toConstr :: FormCreateTranslation -> Constr
$cdataTypeOf :: FormCreateTranslation -> DataType
dataTypeOf :: FormCreateTranslation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranslation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateTranslation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranslation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateTranslation)
$cgmapT :: (forall b. Data b => b -> b)
-> FormCreateTranslation -> FormCreateTranslation
gmapT :: (forall b. Data b => b -> b)
-> FormCreateTranslation -> FormCreateTranslation
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateTranslation -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateTranslation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateTranslation -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateTranslation -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateTranslation -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateTranslation -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateTranslation -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateTranslation -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateTranslation -> m FormCreateTranslation
Data)
instance FromForm FormCreateTranslation
instance ToForm FormCreateTranslation
data FormCreateFile = FormCreateFile
{ FormCreateFile -> FilePath
createFileFile :: FilePath
, FormCreateFile -> Text
createFilePurpose :: Text
} deriving (Int -> FormCreateFile -> ShowS
[FormCreateFile] -> ShowS
FormCreateFile -> FilePath
(Int -> FormCreateFile -> ShowS)
-> (FormCreateFile -> FilePath)
-> ([FormCreateFile] -> ShowS)
-> Show FormCreateFile
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormCreateFile -> ShowS
showsPrec :: Int -> FormCreateFile -> ShowS
$cshow :: FormCreateFile -> FilePath
show :: FormCreateFile -> FilePath
$cshowList :: [FormCreateFile] -> ShowS
showList :: [FormCreateFile] -> ShowS
Show, FormCreateFile -> FormCreateFile -> Bool
(FormCreateFile -> FormCreateFile -> Bool)
-> (FormCreateFile -> FormCreateFile -> Bool) -> Eq FormCreateFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormCreateFile -> FormCreateFile -> Bool
== :: FormCreateFile -> FormCreateFile -> Bool
$c/= :: FormCreateFile -> FormCreateFile -> Bool
/= :: FormCreateFile -> FormCreateFile -> Bool
Eq, (forall x. FormCreateFile -> Rep FormCreateFile x)
-> (forall x. Rep FormCreateFile x -> FormCreateFile)
-> Generic FormCreateFile
forall x. Rep FormCreateFile x -> FormCreateFile
forall x. FormCreateFile -> Rep FormCreateFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FormCreateFile -> Rep FormCreateFile x
from :: forall x. FormCreateFile -> Rep FormCreateFile x
$cto :: forall x. Rep FormCreateFile x -> FormCreateFile
to :: forall x. Rep FormCreateFile x -> FormCreateFile
Generic, Typeable FormCreateFile
Typeable FormCreateFile =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FormCreateFile -> c FormCreateFile)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateFile)
-> (FormCreateFile -> Constr)
-> (FormCreateFile -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateFile))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateFile))
-> ((forall b. Data b => b -> b)
-> FormCreateFile -> FormCreateFile)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r)
-> (forall u.
(forall d. Data d => d -> u) -> FormCreateFile -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateFile -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile)
-> Data FormCreateFile
FormCreateFile -> Constr
FormCreateFile -> DataType
(forall b. Data b => b -> b) -> FormCreateFile -> FormCreateFile
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateFile -> u
forall u. (forall d. Data d => d -> u) -> FormCreateFile -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateFile
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FormCreateFile -> c FormCreateFile
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateFile)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateFile)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FormCreateFile -> c FormCreateFile
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FormCreateFile -> c FormCreateFile
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateFile
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateFile
$ctoConstr :: FormCreateFile -> Constr
toConstr :: FormCreateFile -> Constr
$cdataTypeOf :: FormCreateFile -> DataType
dataTypeOf :: FormCreateFile -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateFile)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateFile)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateFile)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateFile)
$cgmapT :: (forall b. Data b => b -> b) -> FormCreateFile -> FormCreateFile
gmapT :: (forall b. Data b => b -> b) -> FormCreateFile -> FormCreateFile
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateFile -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FormCreateFile -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> FormCreateFile -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateFile -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateFile -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateFile -> m FormCreateFile
Data)
instance FromForm FormCreateFile
instance ToForm FormCreateFile
data FormCreateImageEdit = FormCreateImageEdit
{ FormCreateImageEdit -> FilePath
createImageEditImage :: FilePath
, FormCreateImageEdit -> Text
createImageEditPrompt :: Text
, FormCreateImageEdit -> FilePath
createImageEditMask :: FilePath
, FormCreateImageEdit -> Int
createImageEditN :: Int
, FormCreateImageEdit -> Text
createImageEditSize :: Text
, FormCreateImageEdit -> Text
createImageEditResponseFormat :: Text
, FormCreateImageEdit -> Text
createImageEditUser :: Text
} deriving (Int -> FormCreateImageEdit -> ShowS
[FormCreateImageEdit] -> ShowS
FormCreateImageEdit -> FilePath
(Int -> FormCreateImageEdit -> ShowS)
-> (FormCreateImageEdit -> FilePath)
-> ([FormCreateImageEdit] -> ShowS)
-> Show FormCreateImageEdit
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormCreateImageEdit -> ShowS
showsPrec :: Int -> FormCreateImageEdit -> ShowS
$cshow :: FormCreateImageEdit -> FilePath
show :: FormCreateImageEdit -> FilePath
$cshowList :: [FormCreateImageEdit] -> ShowS
showList :: [FormCreateImageEdit] -> ShowS
Show, FormCreateImageEdit -> FormCreateImageEdit -> Bool
(FormCreateImageEdit -> FormCreateImageEdit -> Bool)
-> (FormCreateImageEdit -> FormCreateImageEdit -> Bool)
-> Eq FormCreateImageEdit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormCreateImageEdit -> FormCreateImageEdit -> Bool
== :: FormCreateImageEdit -> FormCreateImageEdit -> Bool
$c/= :: FormCreateImageEdit -> FormCreateImageEdit -> Bool
/= :: FormCreateImageEdit -> FormCreateImageEdit -> Bool
Eq, (forall x. FormCreateImageEdit -> Rep FormCreateImageEdit x)
-> (forall x. Rep FormCreateImageEdit x -> FormCreateImageEdit)
-> Generic FormCreateImageEdit
forall x. Rep FormCreateImageEdit x -> FormCreateImageEdit
forall x. FormCreateImageEdit -> Rep FormCreateImageEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FormCreateImageEdit -> Rep FormCreateImageEdit x
from :: forall x. FormCreateImageEdit -> Rep FormCreateImageEdit x
$cto :: forall x. Rep FormCreateImageEdit x -> FormCreateImageEdit
to :: forall x. Rep FormCreateImageEdit x -> FormCreateImageEdit
Generic, Typeable FormCreateImageEdit
Typeable FormCreateImageEdit =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageEdit
-> c FormCreateImageEdit)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageEdit)
-> (FormCreateImageEdit -> Constr)
-> (FormCreateImageEdit -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateImageEdit))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageEdit))
-> ((forall b. Data b => b -> b)
-> FormCreateImageEdit -> FormCreateImageEdit)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r)
-> (forall u.
(forall d. Data d => d -> u) -> FormCreateImageEdit -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateImageEdit -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit)
-> Data FormCreateImageEdit
FormCreateImageEdit -> Constr
FormCreateImageEdit -> DataType
(forall b. Data b => b -> b)
-> FormCreateImageEdit -> FormCreateImageEdit
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateImageEdit -> u
forall u.
(forall d. Data d => d -> u) -> FormCreateImageEdit -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageEdit
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageEdit
-> c FormCreateImageEdit
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateImageEdit)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageEdit)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageEdit
-> c FormCreateImageEdit
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageEdit
-> c FormCreateImageEdit
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageEdit
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageEdit
$ctoConstr :: FormCreateImageEdit -> Constr
toConstr :: FormCreateImageEdit -> Constr
$cdataTypeOf :: FormCreateImageEdit -> DataType
dataTypeOf :: FormCreateImageEdit -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateImageEdit)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateImageEdit)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageEdit)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageEdit)
$cgmapT :: (forall b. Data b => b -> b)
-> FormCreateImageEdit -> FormCreateImageEdit
gmapT :: (forall b. Data b => b -> b)
-> FormCreateImageEdit -> FormCreateImageEdit
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormCreateImageEdit -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateImageEdit -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateImageEdit -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateImageEdit -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FormCreateImageEdit -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageEdit -> m FormCreateImageEdit
Data)
instance FromForm FormCreateImageEdit
instance ToForm FormCreateImageEdit
data FormCreateImageVariation = FormCreateImageVariation
{ FormCreateImageVariation -> FilePath
createImageVariationImage :: FilePath
, FormCreateImageVariation -> Int
createImageVariationN :: Int
, FormCreateImageVariation -> Text
createImageVariationResponseFormat :: Text
, FormCreateImageVariation -> Text
createImageVariationSize :: Text
, FormCreateImageVariation -> Text
createImageVariationUser :: Text
} deriving (Int -> FormCreateImageVariation -> ShowS
[FormCreateImageVariation] -> ShowS
FormCreateImageVariation -> FilePath
(Int -> FormCreateImageVariation -> ShowS)
-> (FormCreateImageVariation -> FilePath)
-> ([FormCreateImageVariation] -> ShowS)
-> Show FormCreateImageVariation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormCreateImageVariation -> ShowS
showsPrec :: Int -> FormCreateImageVariation -> ShowS
$cshow :: FormCreateImageVariation -> FilePath
show :: FormCreateImageVariation -> FilePath
$cshowList :: [FormCreateImageVariation] -> ShowS
showList :: [FormCreateImageVariation] -> ShowS
Show, FormCreateImageVariation -> FormCreateImageVariation -> Bool
(FormCreateImageVariation -> FormCreateImageVariation -> Bool)
-> (FormCreateImageVariation -> FormCreateImageVariation -> Bool)
-> Eq FormCreateImageVariation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormCreateImageVariation -> FormCreateImageVariation -> Bool
== :: FormCreateImageVariation -> FormCreateImageVariation -> Bool
$c/= :: FormCreateImageVariation -> FormCreateImageVariation -> Bool
/= :: FormCreateImageVariation -> FormCreateImageVariation -> Bool
Eq, (forall x.
FormCreateImageVariation -> Rep FormCreateImageVariation x)
-> (forall x.
Rep FormCreateImageVariation x -> FormCreateImageVariation)
-> Generic FormCreateImageVariation
forall x.
Rep FormCreateImageVariation x -> FormCreateImageVariation
forall x.
FormCreateImageVariation -> Rep FormCreateImageVariation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
FormCreateImageVariation -> Rep FormCreateImageVariation x
from :: forall x.
FormCreateImageVariation -> Rep FormCreateImageVariation x
$cto :: forall x.
Rep FormCreateImageVariation x -> FormCreateImageVariation
to :: forall x.
Rep FormCreateImageVariation x -> FormCreateImageVariation
Generic, Typeable FormCreateImageVariation
Typeable FormCreateImageVariation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageVariation
-> c FormCreateImageVariation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageVariation)
-> (FormCreateImageVariation -> Constr)
-> (FormCreateImageVariation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c FormCreateImageVariation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageVariation))
-> ((forall b. Data b => b -> b)
-> FormCreateImageVariation -> FormCreateImageVariation)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> FormCreateImageVariation -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> FormCreateImageVariation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation)
-> Data FormCreateImageVariation
FormCreateImageVariation -> Constr
FormCreateImageVariation -> DataType
(forall b. Data b => b -> b)
-> FormCreateImageVariation -> FormCreateImageVariation
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> FormCreateImageVariation -> u
forall u.
(forall d. Data d => d -> u) -> FormCreateImageVariation -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageVariation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageVariation
-> c FormCreateImageVariation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateImageVariation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageVariation)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageVariation
-> c FormCreateImageVariation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FormCreateImageVariation
-> c FormCreateImageVariation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageVariation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormCreateImageVariation
$ctoConstr :: FormCreateImageVariation -> Constr
toConstr :: FormCreateImageVariation -> Constr
$cdataTypeOf :: FormCreateImageVariation -> DataType
dataTypeOf :: FormCreateImageVariation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateImageVariation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormCreateImageVariation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageVariation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormCreateImageVariation)
$cgmapT :: (forall b. Data b => b -> b)
-> FormCreateImageVariation -> FormCreateImageVariation
gmapT :: (forall b. Data b => b -> b)
-> FormCreateImageVariation -> FormCreateImageVariation
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FormCreateImageVariation
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateImageVariation -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> FormCreateImageVariation -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> FormCreateImageVariation -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> FormCreateImageVariation -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FormCreateImageVariation -> m FormCreateImageVariation
Data)
instance FromForm FormCreateImageVariation
instance ToForm FormCreateImageVariation
newtype QueryList (p :: CollectionFormat) a = QueryList
{ forall (p :: CollectionFormat) a. QueryList p a -> [a]
fromQueryList :: [a]
} deriving ((forall a b. (a -> b) -> QueryList p a -> QueryList p b)
-> (forall a b. a -> QueryList p b -> QueryList p a)
-> Functor (QueryList p)
forall a b. a -> QueryList p b -> QueryList p a
forall a b. (a -> b) -> QueryList p a -> QueryList p b
forall (p :: CollectionFormat) a b.
a -> QueryList p b -> QueryList p a
forall (p :: CollectionFormat) a b.
(a -> b) -> QueryList p a -> QueryList p b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (p :: CollectionFormat) a b.
(a -> b) -> QueryList p a -> QueryList p b
fmap :: forall a b. (a -> b) -> QueryList p a -> QueryList p b
$c<$ :: forall (p :: CollectionFormat) a b.
a -> QueryList p b -> QueryList p a
<$ :: forall a b. a -> QueryList p b -> QueryList p a
Functor, Functor (QueryList p)
Functor (QueryList p) =>
(forall a. a -> QueryList p a)
-> (forall a b.
QueryList p (a -> b) -> QueryList p a -> QueryList p b)
-> (forall a b c.
(a -> b -> c) -> QueryList p a -> QueryList p b -> QueryList p c)
-> (forall a b. QueryList p a -> QueryList p b -> QueryList p b)
-> (forall a b. QueryList p a -> QueryList p b -> QueryList p a)
-> Applicative (QueryList p)
forall a. a -> QueryList p a
forall a b. QueryList p a -> QueryList p b -> QueryList p a
forall a b. QueryList p a -> QueryList p b -> QueryList p b
forall a b. QueryList p (a -> b) -> QueryList p a -> QueryList p b
forall a b c.
(a -> b -> c) -> QueryList p a -> QueryList p b -> QueryList p c
forall (p :: CollectionFormat). Functor (QueryList p)
forall (p :: CollectionFormat) a. a -> QueryList p a
forall (p :: CollectionFormat) a b.
QueryList p a -> QueryList p b -> QueryList p a
forall (p :: CollectionFormat) a b.
QueryList p a -> QueryList p b -> QueryList p b
forall (p :: CollectionFormat) a b.
QueryList p (a -> b) -> QueryList p a -> QueryList p b
forall (p :: CollectionFormat) a b c.
(a -> b -> c) -> QueryList p a -> QueryList p b -> QueryList p c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall (p :: CollectionFormat) a. a -> QueryList p a
pure :: forall a. a -> QueryList p a
$c<*> :: forall (p :: CollectionFormat) a b.
QueryList p (a -> b) -> QueryList p a -> QueryList p b
<*> :: forall a b. QueryList p (a -> b) -> QueryList p a -> QueryList p b
$cliftA2 :: forall (p :: CollectionFormat) a b c.
(a -> b -> c) -> QueryList p a -> QueryList p b -> QueryList p c
liftA2 :: forall a b c.
(a -> b -> c) -> QueryList p a -> QueryList p b -> QueryList p c
$c*> :: forall (p :: CollectionFormat) a b.
QueryList p a -> QueryList p b -> QueryList p b
*> :: forall a b. QueryList p a -> QueryList p b -> QueryList p b
$c<* :: forall (p :: CollectionFormat) a b.
QueryList p a -> QueryList p b -> QueryList p a
<* :: forall a b. QueryList p a -> QueryList p b -> QueryList p a
Applicative, Applicative (QueryList p)
Applicative (QueryList p) =>
(forall a b.
QueryList p a -> (a -> QueryList p b) -> QueryList p b)
-> (forall a b. QueryList p a -> QueryList p b -> QueryList p b)
-> (forall a. a -> QueryList p a)
-> Monad (QueryList p)
forall a. a -> QueryList p a
forall a b. QueryList p a -> QueryList p b -> QueryList p b
forall a b. QueryList p a -> (a -> QueryList p b) -> QueryList p b
forall (p :: CollectionFormat). Applicative (QueryList p)
forall (p :: CollectionFormat) a. a -> QueryList p a
forall (p :: CollectionFormat) a b.
QueryList p a -> QueryList p b -> QueryList p b
forall (p :: CollectionFormat) a b.
QueryList p a -> (a -> QueryList p b) -> QueryList p b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall (p :: CollectionFormat) a b.
QueryList p a -> (a -> QueryList p b) -> QueryList p b
>>= :: forall a b. QueryList p a -> (a -> QueryList p b) -> QueryList p b
$c>> :: forall (p :: CollectionFormat) a b.
QueryList p a -> QueryList p b -> QueryList p b
>> :: forall a b. QueryList p a -> QueryList p b -> QueryList p b
$creturn :: forall (p :: CollectionFormat) a. a -> QueryList p a
return :: forall a. a -> QueryList p a
Monad, (forall m. Monoid m => QueryList p m -> m)
-> (forall m a. Monoid m => (a -> m) -> QueryList p a -> m)
-> (forall m a. Monoid m => (a -> m) -> QueryList p a -> m)
-> (forall a b. (a -> b -> b) -> b -> QueryList p a -> b)
-> (forall a b. (a -> b -> b) -> b -> QueryList p a -> b)
-> (forall b a. (b -> a -> b) -> b -> QueryList p a -> b)
-> (forall b a. (b -> a -> b) -> b -> QueryList p a -> b)
-> (forall a. (a -> a -> a) -> QueryList p a -> a)
-> (forall a. (a -> a -> a) -> QueryList p a -> a)
-> (forall a. QueryList p a -> [a])
-> (forall a. QueryList p a -> Bool)
-> (forall a. QueryList p a -> Int)
-> (forall a. Eq a => a -> QueryList p a -> Bool)
-> (forall a. Ord a => QueryList p a -> a)
-> (forall a. Ord a => QueryList p a -> a)
-> (forall a. Num a => QueryList p a -> a)
-> (forall a. Num a => QueryList p a -> a)
-> Foldable (QueryList p)
forall a. Eq a => a -> QueryList p a -> Bool
forall a. Num a => QueryList p a -> a
forall a. Ord a => QueryList p a -> a
forall m. Monoid m => QueryList p m -> m
forall a. QueryList p a -> Bool
forall a. QueryList p a -> Int
forall a. QueryList p a -> [a]
forall a. (a -> a -> a) -> QueryList p a -> a
forall m a. Monoid m => (a -> m) -> QueryList p a -> m
forall b a. (b -> a -> b) -> b -> QueryList p a -> b
forall a b. (a -> b -> b) -> b -> QueryList p a -> b
forall (p :: CollectionFormat) a.
Eq a =>
a -> QueryList p a -> Bool
forall (p :: CollectionFormat) a. Num a => QueryList p a -> a
forall (p :: CollectionFormat) a. Ord a => QueryList p a -> a
forall (p :: CollectionFormat) m. Monoid m => QueryList p m -> m
forall (p :: CollectionFormat) a. QueryList p a -> Bool
forall (p :: CollectionFormat) a. QueryList p a -> Int
forall (p :: CollectionFormat) a. QueryList p a -> [a]
forall (p :: CollectionFormat) a.
(a -> a -> a) -> QueryList p a -> a
forall (p :: CollectionFormat) m a.
Monoid m =>
(a -> m) -> QueryList p a -> m
forall (p :: CollectionFormat) b a.
(b -> a -> b) -> b -> QueryList p a -> b
forall (p :: CollectionFormat) a b.
(a -> b -> b) -> b -> QueryList p a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (p :: CollectionFormat) m. Monoid m => QueryList p m -> m
fold :: forall m. Monoid m => QueryList p m -> m
$cfoldMap :: forall (p :: CollectionFormat) m a.
Monoid m =>
(a -> m) -> QueryList p a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> QueryList p a -> m
$cfoldMap' :: forall (p :: CollectionFormat) m a.
Monoid m =>
(a -> m) -> QueryList p a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> QueryList p a -> m
$cfoldr :: forall (p :: CollectionFormat) a b.
(a -> b -> b) -> b -> QueryList p a -> b
foldr :: forall a b. (a -> b -> b) -> b -> QueryList p a -> b
$cfoldr' :: forall (p :: CollectionFormat) a b.
(a -> b -> b) -> b -> QueryList p a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> QueryList p a -> b
$cfoldl :: forall (p :: CollectionFormat) b a.
(b -> a -> b) -> b -> QueryList p a -> b
foldl :: forall b a. (b -> a -> b) -> b -> QueryList p a -> b
$cfoldl' :: forall (p :: CollectionFormat) b a.
(b -> a -> b) -> b -> QueryList p a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> QueryList p a -> b
$cfoldr1 :: forall (p :: CollectionFormat) a.
(a -> a -> a) -> QueryList p a -> a
foldr1 :: forall a. (a -> a -> a) -> QueryList p a -> a
$cfoldl1 :: forall (p :: CollectionFormat) a.
(a -> a -> a) -> QueryList p a -> a
foldl1 :: forall a. (a -> a -> a) -> QueryList p a -> a
$ctoList :: forall (p :: CollectionFormat) a. QueryList p a -> [a]
toList :: forall a. QueryList p a -> [a]
$cnull :: forall (p :: CollectionFormat) a. QueryList p a -> Bool
null :: forall a. QueryList p a -> Bool
$clength :: forall (p :: CollectionFormat) a. QueryList p a -> Int
length :: forall a. QueryList p a -> Int
$celem :: forall (p :: CollectionFormat) a.
Eq a =>
a -> QueryList p a -> Bool
elem :: forall a. Eq a => a -> QueryList p a -> Bool
$cmaximum :: forall (p :: CollectionFormat) a. Ord a => QueryList p a -> a
maximum :: forall a. Ord a => QueryList p a -> a
$cminimum :: forall (p :: CollectionFormat) a. Ord a => QueryList p a -> a
minimum :: forall a. Ord a => QueryList p a -> a
$csum :: forall (p :: CollectionFormat) a. Num a => QueryList p a -> a
sum :: forall a. Num a => QueryList p a -> a
$cproduct :: forall (p :: CollectionFormat) a. Num a => QueryList p a -> a
product :: forall a. Num a => QueryList p a -> a
Foldable, Functor (QueryList p)
Foldable (QueryList p)
(Functor (QueryList p), Foldable (QueryList p)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> QueryList p a -> f (QueryList p b))
-> (forall (f :: * -> *) a.
Applicative f =>
QueryList p (f a) -> f (QueryList p a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> QueryList p a -> m (QueryList p b))
-> (forall (m :: * -> *) a.
Monad m =>
QueryList p (m a) -> m (QueryList p a))
-> Traversable (QueryList p)
forall (p :: CollectionFormat). Functor (QueryList p)
forall (p :: CollectionFormat). Foldable (QueryList p)
forall (p :: CollectionFormat) (m :: * -> *) a.
Monad m =>
QueryList p (m a) -> m (QueryList p a)
forall (p :: CollectionFormat) (f :: * -> *) a.
Applicative f =>
QueryList p (f a) -> f (QueryList p a)
forall (p :: CollectionFormat) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> QueryList p a -> m (QueryList p b)
forall (p :: CollectionFormat) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> QueryList p a -> f (QueryList p b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
QueryList p (m a) -> m (QueryList p a)
forall (f :: * -> *) a.
Applicative f =>
QueryList p (f a) -> f (QueryList p a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> QueryList p a -> m (QueryList p b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> QueryList p a -> f (QueryList p b)
$ctraverse :: forall (p :: CollectionFormat) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> QueryList p a -> f (QueryList p b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> QueryList p a -> f (QueryList p b)
$csequenceA :: forall (p :: CollectionFormat) (f :: * -> *) a.
Applicative f =>
QueryList p (f a) -> f (QueryList p a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
QueryList p (f a) -> f (QueryList p a)
$cmapM :: forall (p :: CollectionFormat) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> QueryList p a -> m (QueryList p b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> QueryList p a -> m (QueryList p b)
$csequence :: forall (p :: CollectionFormat) (m :: * -> *) a.
Monad m =>
QueryList p (m a) -> m (QueryList p a)
sequence :: forall (m :: * -> *) a.
Monad m =>
QueryList p (m a) -> m (QueryList p a)
Traversable)
data CollectionFormat
= CommaSeparated
| SpaceSeparated
| TabSeparated
| PipeSeparated
| MultiParamArray
instance FromHttpApiData a => FromHttpApiData (QueryList 'CommaSeparated a) where
parseQueryParam :: Text -> Either Text (QueryList 'CommaSeparated a)
parseQueryParam = Char -> Text -> Either Text (QueryList 'CommaSeparated a)
forall a (p :: CollectionFormat).
FromHttpApiData a =>
Char -> Text -> Either Text (QueryList p a)
parseSeparatedQueryList Char
','
instance FromHttpApiData a => FromHttpApiData (QueryList 'TabSeparated a) where
parseQueryParam :: Text -> Either Text (QueryList 'TabSeparated a)
parseQueryParam = Char -> Text -> Either Text (QueryList 'TabSeparated a)
forall a (p :: CollectionFormat).
FromHttpApiData a =>
Char -> Text -> Either Text (QueryList p a)
parseSeparatedQueryList Char
'\t'
instance FromHttpApiData a => FromHttpApiData (QueryList 'SpaceSeparated a) where
parseQueryParam :: Text -> Either Text (QueryList 'SpaceSeparated a)
parseQueryParam = Char -> Text -> Either Text (QueryList 'SpaceSeparated a)
forall a (p :: CollectionFormat).
FromHttpApiData a =>
Char -> Text -> Either Text (QueryList p a)
parseSeparatedQueryList Char
' '
instance FromHttpApiData a => FromHttpApiData (QueryList 'PipeSeparated a) where
parseQueryParam :: Text -> Either Text (QueryList 'PipeSeparated a)
parseQueryParam = Char -> Text -> Either Text (QueryList 'PipeSeparated a)
forall a (p :: CollectionFormat).
FromHttpApiData a =>
Char -> Text -> Either Text (QueryList p a)
parseSeparatedQueryList Char
'|'
instance FromHttpApiData a => FromHttpApiData (QueryList 'MultiParamArray a) where
parseQueryParam :: Text -> Either Text (QueryList 'MultiParamArray a)
parseQueryParam = FilePath -> Text -> Either Text (QueryList 'MultiParamArray a)
forall a. HasCallStack => FilePath -> a
error FilePath
"unimplemented FromHttpApiData for MultiParamArray collection format"
parseSeparatedQueryList :: FromHttpApiData a => Char -> Text -> Either Text (QueryList p a)
parseSeparatedQueryList :: forall a (p :: CollectionFormat).
FromHttpApiData a =>
Char -> Text -> Either Text (QueryList p a)
parseSeparatedQueryList Char
char = ([a] -> QueryList p a)
-> Either Text [a] -> Either Text (QueryList p a)
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> QueryList p a
forall (p :: CollectionFormat) a. [a] -> QueryList p a
QueryList (Either Text [a] -> Either Text (QueryList p a))
-> (Text -> Either Text [a]) -> Text -> Either Text (QueryList p a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Either Text a) -> [Text] -> Either Text [a]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam ([Text] -> Either Text [a])
-> (Text -> [Text]) -> Text -> Either Text [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
char)
instance ToHttpApiData a => ToHttpApiData (QueryList 'CommaSeparated a) where
toQueryParam :: QueryList 'CommaSeparated a -> Text
toQueryParam = Char -> QueryList 'CommaSeparated a -> Text
forall a (p :: CollectionFormat).
ToHttpApiData a =>
Char -> QueryList p a -> Text
formatSeparatedQueryList Char
','
instance ToHttpApiData a => ToHttpApiData (QueryList 'TabSeparated a) where
toQueryParam :: QueryList 'TabSeparated a -> Text
toQueryParam = Char -> QueryList 'TabSeparated a -> Text
forall a (p :: CollectionFormat).
ToHttpApiData a =>
Char -> QueryList p a -> Text
formatSeparatedQueryList Char
'\t'
instance ToHttpApiData a => ToHttpApiData (QueryList 'SpaceSeparated a) where
toQueryParam :: QueryList 'SpaceSeparated a -> Text
toQueryParam = Char -> QueryList 'SpaceSeparated a -> Text
forall a (p :: CollectionFormat).
ToHttpApiData a =>
Char -> QueryList p a -> Text
formatSeparatedQueryList Char
' '
instance ToHttpApiData a => ToHttpApiData (QueryList 'PipeSeparated a) where
toQueryParam :: QueryList 'PipeSeparated a -> Text
toQueryParam = Char -> QueryList 'PipeSeparated a -> Text
forall a (p :: CollectionFormat).
ToHttpApiData a =>
Char -> QueryList p a -> Text
formatSeparatedQueryList Char
'|'
instance ToHttpApiData a => ToHttpApiData (QueryList 'MultiParamArray a) where
toQueryParam :: QueryList 'MultiParamArray a -> Text
toQueryParam = FilePath -> QueryList 'MultiParamArray a -> Text
forall a. HasCallStack => FilePath -> a
error FilePath
"unimplemented ToHttpApiData for MultiParamArray collection format"
formatSeparatedQueryList :: ToHttpApiData a => Char -> QueryList p a -> Text
formatSeparatedQueryList :: forall a (p :: CollectionFormat).
ToHttpApiData a =>
Char -> QueryList p a -> Text
formatSeparatedQueryList Char
char = Text -> [Text] -> Text
T.intercalate (Char -> Text
T.singleton Char
char) ([Text] -> Text)
-> (QueryList p a -> [Text]) -> QueryList p a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Text) -> [a] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam ([a] -> [Text])
-> (QueryList p a -> [a]) -> QueryList p a -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueryList p a -> [a]
forall (p :: CollectionFormat) a. QueryList p a -> [a]
fromQueryList
data AudioMpeg deriving Typeable
instance Accept AudioMpeg where
contentType :: Proxy AudioMpeg -> MediaType
contentType Proxy AudioMpeg
_ = ByteString
"audio" ByteString -> ByteString -> MediaType
M.// ByteString
"mpeg"
instance MimeRender AudioMpeg ByteString where
mimeRender :: Proxy AudioMpeg -> ByteString -> ByteString
mimeRender Proxy AudioMpeg
_ = ByteString -> ByteString
fromStrict
instance MimeUnrender AudioMpeg ByteString where
mimeUnrender :: Proxy AudioMpeg -> ByteString -> Either FilePath ByteString
mimeUnrender Proxy AudioMpeg
_ = ByteString -> Either FilePath ByteString
forall a b. b -> Either a b
Right (ByteString -> Either FilePath ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> Either FilePath ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict
type OpenAIAPI
= Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> Capture "run_id" Text :> "cancel" :> Verb 'POST 200 '[JSON] RunObject
:<|> Protected :> "assistants" :> ReqBody '[JSON] CreateAssistantRequest :> Verb 'POST 200 '[JSON] AssistantObject
:<|> Protected :> "assistants" :> Capture "assistant_id" Text :> "files" :> ReqBody '[JSON] CreateAssistantFileRequest :> Verb 'POST 200 '[JSON] AssistantFileObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "messages" :> ReqBody '[JSON] CreateMessageRequest :> Verb 'POST 200 '[JSON] MessageObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> ReqBody '[JSON] CreateRunRequest :> Verb 'POST 200 '[JSON] RunObject
:<|> Protected :> "threads" :> ReqBody '[JSON] CreateThreadRequest :> Verb 'POST 200 '[JSON] ThreadObject
:<|> Protected :> "threads" :> "runs" :> ReqBody '[JSON] CreateThreadAndRunRequest :> Verb 'POST 200 '[JSON] RunObject
:<|> Protected :> "assistants" :> Capture "assistant_id" Text :> Verb 'DELETE 200 '[JSON] DeleteAssistantResponse
:<|> Protected :> "assistants" :> Capture "assistant_id" Text :> "files" :> Capture "file_id" Text :> Verb 'DELETE 200 '[JSON] DeleteAssistantFileResponse
:<|> Protected :> "threads" :> Capture "thread_id" Text :> Verb 'DELETE 200 '[JSON] DeleteThreadResponse
:<|> Protected :> "assistants" :> Capture "assistant_id" Text :> Verb 'GET 200 '[JSON] AssistantObject
:<|> Protected :> "assistants" :> Capture "assistant_id" Text :> "files" :> Capture "file_id" Text :> Verb 'GET 200 '[JSON] AssistantFileObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "messages" :> Capture "message_id" Text :> Verb 'GET 200 '[JSON] MessageObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "messages" :> Capture "message_id" Text :> "files" :> Capture "file_id" Text :> Verb 'GET 200 '[JSON] MessageFileObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> Capture "run_id" Text :> Verb 'GET 200 '[JSON] RunObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> Capture "run_id" Text :> "steps" :> Capture "step_id" Text :> Verb 'GET 200 '[JSON] RunStepObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> Verb 'GET 200 '[JSON] ThreadObject
:<|> Protected :> "assistants" :> Capture "assistant_id" Text :> "files" :> QueryParam "limit" Int :> QueryParam "order" Text :> QueryParam "after" Text :> QueryParam "before" Text :> Verb 'GET 200 '[JSON] ListAssistantFilesResponse
:<|> Protected :> "assistants" :> QueryParam "limit" Int :> QueryParam "order" Text :> QueryParam "after" Text :> QueryParam "before" Text :> Verb 'GET 200 '[JSON] ListAssistantsResponse
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "messages" :> Capture "message_id" Text :> "files" :> QueryParam "limit" Int :> QueryParam "order" Text :> QueryParam "after" Text :> QueryParam "before" Text :> Verb 'GET 200 '[JSON] ListMessageFilesResponse
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "messages" :> QueryParam "limit" Int :> QueryParam "order" Text :> QueryParam "after" Text :> QueryParam "before" Text :> Verb 'GET 200 '[JSON] ListMessagesResponse
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> Capture "run_id" Text :> "steps" :> QueryParam "limit" Int :> QueryParam "order" Text :> QueryParam "after" Text :> QueryParam "before" Text :> Verb 'GET 200 '[JSON] ListRunStepsResponse
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> QueryParam "limit" Int :> QueryParam "order" Text :> QueryParam "after" Text :> QueryParam "before" Text :> Verb 'GET 200 '[JSON] ListRunsResponse
:<|> Protected :> "assistants" :> Capture "assistant_id" Text :> ReqBody '[JSON] ModifyAssistantRequest :> Verb 'POST 200 '[JSON] AssistantObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "messages" :> Capture "message_id" Text :> ReqBody '[JSON] ModifyMessageRequest :> Verb 'POST 200 '[JSON] MessageObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> Capture "run_id" Text :> ReqBody '[JSON] ModifyRunRequest :> Verb 'POST 200 '[JSON] RunObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> ReqBody '[JSON] ModifyThreadRequest :> Verb 'POST 200 '[JSON] ThreadObject
:<|> Protected :> "threads" :> Capture "thread_id" Text :> "runs" :> Capture "run_id" Text :> "submit_tool_outputs" :> ReqBody '[JSON] SubmitToolOutputsRunRequest :> Verb 'POST 200 '[JSON] RunObject
:<|> Protected :> "audio" :> "speech" :> ReqBody '[JSON] CreateSpeechRequest :> Verb 'POST 200 '[AudioMpeg] ByteString
:<|> Protected :> "audio" :> "transcriptions" :> ReqBody '[FormUrlEncoded] FormCreateTranscription :> Verb 'POST 200 '[JSON] CreateTranscription200Response
:<|> Protected :> "audio" :> "translations" :> ReqBody '[FormUrlEncoded] FormCreateTranslation :> Verb 'POST 200 '[JSON] CreateTranslation200Response
:<|> Protected :> "chat" :> "completions" :> ReqBody '[JSON] CreateChatCompletionRequest :> Verb 'POST 200 '[JSON] CreateChatCompletionResponse
:<|> Protected :> "completions" :> ReqBody '[JSON] CreateCompletionRequest :> Verb 'POST 200 '[JSON] CreateCompletionResponse
:<|> Protected :> "embeddings" :> ReqBody '[JSON] CreateEmbeddingRequest :> Verb 'POST 200 '[JSON] CreateEmbeddingResponse
:<|> Protected :> "files" :> ReqBody '[FormUrlEncoded] FormCreateFile :> Verb 'POST 200 '[JSON] OpenAIFile
:<|> Protected :> "files" :> Capture "file_id" Text :> Verb 'DELETE 200 '[JSON] DeleteFileResponse
:<|> Protected :> "files" :> Capture "file_id" Text :> "content" :> Verb 'GET 200 '[JSON] Text
:<|> Protected :> "files" :> QueryParam "purpose" Text :> Verb 'GET 200 '[JSON] ListFilesResponse
:<|> Protected :> "files" :> Capture "file_id" Text :> Verb 'GET 200 '[JSON] OpenAIFile
:<|> Protected :> "fine_tuning" :> "jobs" :> Capture "fine_tuning_job_id" Text :> "cancel" :> Verb 'POST 200 '[JSON] FineTuningJob
:<|> Protected :> "fine_tuning" :> "jobs" :> ReqBody '[JSON] CreateFineTuningJobRequest :> Verb 'POST 200 '[JSON] FineTuningJob
:<|> Protected :> "fine_tuning" :> "jobs" :> Capture "fine_tuning_job_id" Text :> "events" :> QueryParam "after" Text :> QueryParam "limit" Int :> Verb 'GET 200 '[JSON] ListFineTuningJobEventsResponse
:<|> Protected :> "fine_tuning" :> "jobs" :> QueryParam "after" Text :> QueryParam "limit" Int :> Verb 'GET 200 '[JSON] ListPaginatedFineTuningJobsResponse
:<|> Protected :> "fine_tuning" :> "jobs" :> Capture "fine_tuning_job_id" Text :> Verb 'GET 200 '[JSON] FineTuningJob
:<|> Protected :> "images" :> "generations" :> ReqBody '[JSON] CreateImageRequest :> Verb 'POST 200 '[JSON] ImagesResponse
:<|> Protected :> "images" :> "edits" :> ReqBody '[FormUrlEncoded] FormCreateImageEdit :> Verb 'POST 200 '[JSON] ImagesResponse
:<|> Protected :> "images" :> "variations" :> ReqBody '[FormUrlEncoded] FormCreateImageVariation :> Verb 'POST 200 '[JSON] ImagesResponse
:<|> Protected :> "models" :> Capture "model" Text :> Verb 'DELETE 200 '[JSON] DeleteModelResponse
:<|> Protected :> "models" :> Verb 'GET 200 '[JSON] ListModelsResponse
:<|> Protected :> "models" :> Capture "model" Text :> Verb 'GET 200 '[JSON] Model
:<|> Protected :> "moderations" :> ReqBody '[JSON] CreateModerationRequest :> Verb 'POST 200 '[JSON] CreateModerationResponse
:<|> Raw
data Config = Config
{ Config -> FilePath
configUrl :: String
} deriving (Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
/= :: Config -> Config -> Bool
Eq, Eq Config
Eq Config =>
(Config -> Config -> Ordering)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Config)
-> (Config -> Config -> Config)
-> Ord Config
Config -> Config -> Bool
Config -> Config -> Ordering
Config -> Config -> Config
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Config -> Config -> Ordering
compare :: Config -> Config -> Ordering
$c< :: Config -> Config -> Bool
< :: Config -> Config -> Bool
$c<= :: Config -> Config -> Bool
<= :: Config -> Config -> Bool
$c> :: Config -> Config -> Bool
> :: Config -> Config -> Bool
$c>= :: Config -> Config -> Bool
>= :: Config -> Config -> Bool
$cmax :: Config -> Config -> Config
max :: Config -> Config -> Config
$cmin :: Config -> Config -> Config
min :: Config -> Config -> Config
Ord, Int -> Config -> ShowS
[Config] -> ShowS
Config -> FilePath
(Int -> Config -> ShowS)
-> (Config -> FilePath) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Config -> ShowS
showsPrec :: Int -> Config -> ShowS
$cshow :: Config -> FilePath
show :: Config -> FilePath
$cshowList :: [Config] -> ShowS
showList :: [Config] -> ShowS
Show, ReadPrec [Config]
ReadPrec Config
Int -> ReadS Config
ReadS [Config]
(Int -> ReadS Config)
-> ReadS [Config]
-> ReadPrec Config
-> ReadPrec [Config]
-> Read Config
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Config
readsPrec :: Int -> ReadS Config
$creadList :: ReadS [Config]
readList :: ReadS [Config]
$creadPrec :: ReadPrec Config
readPrec :: ReadPrec Config
$creadListPrec :: ReadPrec [Config]
readListPrec :: ReadPrec [Config]
Read)
newtype OpenAIClientError = OpenAIClientError ClientError
deriving (Int -> OpenAIClientError -> ShowS
[OpenAIClientError] -> ShowS
OpenAIClientError -> FilePath
(Int -> OpenAIClientError -> ShowS)
-> (OpenAIClientError -> FilePath)
-> ([OpenAIClientError] -> ShowS)
-> Show OpenAIClientError
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenAIClientError -> ShowS
showsPrec :: Int -> OpenAIClientError -> ShowS
$cshow :: OpenAIClientError -> FilePath
show :: OpenAIClientError -> FilePath
$cshowList :: [OpenAIClientError] -> ShowS
showList :: [OpenAIClientError] -> ShowS
Show, Show OpenAIClientError
Typeable OpenAIClientError
(Typeable OpenAIClientError, Show OpenAIClientError) =>
(OpenAIClientError -> SomeException)
-> (SomeException -> Maybe OpenAIClientError)
-> (OpenAIClientError -> FilePath)
-> Exception OpenAIClientError
SomeException -> Maybe OpenAIClientError
OpenAIClientError -> FilePath
OpenAIClientError -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e) -> (e -> FilePath) -> Exception e
$ctoException :: OpenAIClientError -> SomeException
toException :: OpenAIClientError -> SomeException
$cfromException :: SomeException -> Maybe OpenAIClientError
fromException :: SomeException -> Maybe OpenAIClientError
$cdisplayException :: OpenAIClientError -> FilePath
displayException :: OpenAIClientError -> FilePath
Exception)
data OpenAIBackend a m = OpenAIBackend
{ forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m RunObject
cancelRun :: a -> Text -> Text -> m RunObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateAssistantRequest -> m AssistantObject
createAssistant :: a -> CreateAssistantRequest -> m AssistantObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject
createAssistantFile :: a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> CreateMessageRequest -> m MessageObject
createMessage :: a -> Text -> CreateMessageRequest -> m MessageObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> CreateRunRequest -> m RunObject
createRun :: a -> Text -> CreateRunRequest -> m RunObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateThreadRequest -> m ThreadObject
createThread :: a -> CreateThreadRequest -> m ThreadObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateThreadAndRunRequest -> m RunObject
createThreadAndRun :: a -> CreateThreadAndRunRequest -> m RunObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteAssistantResponse
deleteAssistant :: a -> Text -> m DeleteAssistantResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> m DeleteAssistantFileResponse
deleteAssistantFile :: a -> Text -> Text -> m DeleteAssistantFileResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteThreadResponse
deleteThread :: a -> Text -> m DeleteThreadResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m AssistantObject
getAssistant :: a -> Text -> m AssistantObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m AssistantFileObject
getAssistantFile :: a -> Text -> Text -> m AssistantFileObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m MessageObject
getMessage :: a -> Text -> Text -> m MessageObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> Text -> m MessageFileObject
getMessageFile :: a -> Text -> Text -> Text -> m MessageFileObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m RunObject
getRun :: a -> Text -> Text -> m RunObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> Text -> m RunStepObject
getRunStep :: a -> Text -> Text -> Text -> m RunStepObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m ThreadObject
getThread :: a -> Text -> m ThreadObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantFilesResponse
listAssistantFiles :: a -> Text -> Maybe Int -> Maybe Text -> Maybe Text -> Maybe Text -> m ListAssistantFilesResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantsResponse
listAssistants :: a -> Maybe Int -> Maybe Text -> Maybe Text -> Maybe Text -> m ListAssistantsResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessageFilesResponse
listMessageFiles :: a -> Text -> Text -> Maybe Int -> Maybe Text -> Maybe Text -> Maybe Text -> m ListMessageFilesResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessagesResponse
listMessages :: a -> Text -> Maybe Int -> Maybe Text -> Maybe Text -> Maybe Text -> m ListMessagesResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunStepsResponse
listRunSteps :: a -> Text -> Text -> Maybe Int -> Maybe Text -> Maybe Text -> Maybe Text -> m ListRunStepsResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunsResponse
listRuns :: a -> Text -> Maybe Int -> Maybe Text -> Maybe Text -> Maybe Text -> m ListRunsResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> ModifyAssistantRequest -> m AssistantObject
modifyAssistant :: a -> Text -> ModifyAssistantRequest -> m AssistantObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> ModifyMessageRequest -> m MessageObject
modifyMessage :: a -> Text -> Text -> ModifyMessageRequest -> m MessageObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> ModifyRunRequest -> m RunObject
modifyRun :: a -> Text -> Text -> ModifyRunRequest -> m RunObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> ModifyThreadRequest -> m ThreadObject
modifyThread :: a -> Text -> ModifyThreadRequest -> m ThreadObject
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject
submitToolOuputsToRun :: a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateSpeechRequest -> m ByteString
createSpeech :: a -> CreateSpeechRequest -> m ByteString
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> FormCreateTranscription -> m CreateTranscription200Response
createTranscription :: a -> FormCreateTranscription -> m CreateTranscription200Response
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> FormCreateTranslation -> m CreateTranslation200Response
createTranslation :: a -> FormCreateTranslation -> m CreateTranslation200Response
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> CreateChatCompletionRequest
-> m CreateChatCompletionResponse
createChatCompletion :: a -> CreateChatCompletionRequest -> m CreateChatCompletionResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateCompletionRequest -> m CreateCompletionResponse
createCompletion :: a -> CreateCompletionRequest -> m CreateCompletionResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse
createEmbedding :: a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> FormCreateFile -> m OpenAIFile
createFile :: a -> FormCreateFile -> m OpenAIFile
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteFileResponse
deleteFile :: a -> Text -> m DeleteFileResponse
, forall a (m :: * -> *). OpenAIBackend a m -> a -> Text -> m Text
downloadFile :: a -> Text -> m Text
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Maybe Text -> m ListFilesResponse
listFiles :: a -> Maybe Text -> m ListFilesResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m OpenAIFile
retrieveFile :: a -> Text -> m OpenAIFile
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m FineTuningJob
cancelFineTuningJob :: a -> Text -> m FineTuningJob
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateFineTuningJobRequest -> m FineTuningJob
createFineTuningJob :: a -> CreateFineTuningJobRequest -> m FineTuningJob
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Text
-> Maybe Int
-> m ListFineTuningJobEventsResponse
listFineTuningEvents :: a -> Text -> Maybe Text -> Maybe Int -> m ListFineTuningJobEventsResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Maybe Text
-> Maybe Int
-> m ListPaginatedFineTuningJobsResponse
listPaginatedFineTuningJobs :: a -> Maybe Text -> Maybe Int -> m ListPaginatedFineTuningJobsResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m FineTuningJob
retrieveFineTuningJob :: a -> Text -> m FineTuningJob
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateImageRequest -> m ImagesResponse
createImage :: a -> CreateImageRequest -> m ImagesResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> FormCreateImageEdit -> m ImagesResponse
createImageEdit :: a -> FormCreateImageEdit -> m ImagesResponse
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> FormCreateImageVariation -> m ImagesResponse
createImageVariation :: a -> FormCreateImageVariation -> m ImagesResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteModelResponse
deleteModel :: a -> Text -> m DeleteModelResponse
, forall a (m :: * -> *).
OpenAIBackend a m -> a -> m ListModelsResponse
listModels :: a -> m ListModelsResponse
, forall a (m :: * -> *). OpenAIBackend a m -> a -> Text -> m Model
retrieveModel :: a -> Text -> m Model
, forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateModerationRequest -> m CreateModerationResponse
createModeration :: a -> CreateModerationRequest -> m CreateModerationResponse
}
data OpenAIAuth = OpenAIAuth
{ OpenAIAuth -> ByteString -> Handler (AuthServerData Protected)
lookupUser :: ByteString -> Handler AuthServer
, OpenAIAuth -> Request -> ServerError
authError :: Request -> ServerError
}
newtype OpenAIClient a = OpenAIClient
{ forall a. OpenAIClient a -> ClientEnv -> ExceptT ClientError IO a
runClient :: ClientEnv -> ExceptT ClientError IO a
} deriving (forall a b. (a -> b) -> OpenAIClient a -> OpenAIClient b)
-> (forall a b. a -> OpenAIClient b -> OpenAIClient a)
-> Functor OpenAIClient
forall a b. a -> OpenAIClient b -> OpenAIClient a
forall a b. (a -> b) -> OpenAIClient a -> OpenAIClient b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> OpenAIClient a -> OpenAIClient b
fmap :: forall a b. (a -> b) -> OpenAIClient a -> OpenAIClient b
$c<$ :: forall a b. a -> OpenAIClient b -> OpenAIClient a
<$ :: forall a b. a -> OpenAIClient b -> OpenAIClient a
Functor
instance Applicative OpenAIClient where
pure :: forall a. a -> OpenAIClient a
pure a
x = (ClientEnv -> ExceptT ClientError IO a) -> OpenAIClient a
forall a. (ClientEnv -> ExceptT ClientError IO a) -> OpenAIClient a
OpenAIClient (\ClientEnv
_ -> a -> ExceptT ClientError IO a
forall a. a -> ExceptT ClientError IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x)
(OpenAIClient ClientEnv -> ExceptT ClientError IO (a -> b)
f) <*> :: forall a b.
OpenAIClient (a -> b) -> OpenAIClient a -> OpenAIClient b
<*> (OpenAIClient ClientEnv -> ExceptT ClientError IO a
x) =
(ClientEnv -> ExceptT ClientError IO b) -> OpenAIClient b
forall a. (ClientEnv -> ExceptT ClientError IO a) -> OpenAIClient a
OpenAIClient (\ClientEnv
env -> ClientEnv -> ExceptT ClientError IO (a -> b)
f ClientEnv
env ExceptT ClientError IO (a -> b)
-> ExceptT ClientError IO a -> ExceptT ClientError IO b
forall a b.
ExceptT ClientError IO (a -> b)
-> ExceptT ClientError IO a -> ExceptT ClientError IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ClientEnv -> ExceptT ClientError IO a
x ClientEnv
env)
instance Monad OpenAIClient where
(OpenAIClient ClientEnv -> ExceptT ClientError IO a
a) >>= :: forall a b.
OpenAIClient a -> (a -> OpenAIClient b) -> OpenAIClient b
>>= a -> OpenAIClient b
f =
(ClientEnv -> ExceptT ClientError IO b) -> OpenAIClient b
forall a. (ClientEnv -> ExceptT ClientError IO a) -> OpenAIClient a
OpenAIClient (\ClientEnv
env -> do
a
value <- ClientEnv -> ExceptT ClientError IO a
a ClientEnv
env
OpenAIClient b -> ClientEnv -> ExceptT ClientError IO b
forall a. OpenAIClient a -> ClientEnv -> ExceptT ClientError IO a
runClient (a -> OpenAIClient b
f a
value) ClientEnv
env)
instance MonadIO OpenAIClient where
liftIO :: forall a. IO a -> OpenAIClient a
liftIO IO a
io = (ClientEnv -> ExceptT ClientError IO a) -> OpenAIClient a
forall a. (ClientEnv -> ExceptT ClientError IO a) -> OpenAIClient a
OpenAIClient (\ClientEnv
_ -> IO a -> ExceptT ClientError IO a
forall a. IO a -> ExceptT ClientError IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
io)
createOpenAIClient :: OpenAIBackend AuthClient OpenAIClient
createOpenAIClient :: OpenAIBackend AuthClient OpenAIClient
createOpenAIClient = OpenAIBackend{AuthClient -> OpenAIClient ListModelsResponse
AuthClient
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantsResponse
AuthClient -> Maybe Text -> OpenAIClient ListFilesResponse
AuthClient
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListPaginatedFineTuningJobsResponse
AuthClient -> Text -> OpenAIClient Text
AuthClient -> Text -> OpenAIClient ThreadObject
AuthClient -> Text -> OpenAIClient OpenAIFile
AuthClient -> Text -> OpenAIClient Model
AuthClient -> Text -> OpenAIClient FineTuningJob
AuthClient -> Text -> OpenAIClient DeleteThreadResponse
AuthClient -> Text -> OpenAIClient DeleteModelResponse
AuthClient -> Text -> OpenAIClient DeleteFileResponse
AuthClient -> Text -> OpenAIClient DeleteAssistantResponse
AuthClient -> Text -> OpenAIClient AssistantObject
AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunsResponse
AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessagesResponse
AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantFilesResponse
AuthClient
-> Text
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListFineTuningJobEventsResponse
AuthClient -> Text -> Text -> OpenAIClient RunObject
AuthClient -> Text -> Text -> OpenAIClient MessageObject
AuthClient
-> Text -> Text -> OpenAIClient DeleteAssistantFileResponse
AuthClient -> Text -> Text -> OpenAIClient AssistantFileObject
AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunStepsResponse
AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessageFilesResponse
AuthClient -> Text -> Text -> Text -> OpenAIClient RunStepObject
AuthClient
-> Text -> Text -> Text -> OpenAIClient MessageFileObject
AuthClient
-> Text
-> Text
-> SubmitToolOutputsRunRequest
-> OpenAIClient RunObject
AuthClient
-> Text -> Text -> ModifyRunRequest -> OpenAIClient RunObject
AuthClient
-> Text
-> Text
-> ModifyMessageRequest
-> OpenAIClient MessageObject
AuthClient
-> Text -> ModifyThreadRequest -> OpenAIClient ThreadObject
AuthClient
-> Text -> ModifyAssistantRequest -> OpenAIClient AssistantObject
AuthClient -> Text -> CreateRunRequest -> OpenAIClient RunObject
AuthClient
-> Text -> CreateMessageRequest -> OpenAIClient MessageObject
AuthClient
-> Text
-> CreateAssistantFileRequest
-> OpenAIClient AssistantFileObject
AuthClient -> CreateThreadRequest -> OpenAIClient ThreadObject
AuthClient -> CreateThreadAndRunRequest -> OpenAIClient RunObject
AuthClient -> CreateSpeechRequest -> OpenAIClient ByteString
AuthClient
-> CreateModerationRequest -> OpenAIClient CreateModerationResponse
AuthClient -> CreateImageRequest -> OpenAIClient ImagesResponse
AuthClient
-> CreateFineTuningJobRequest -> OpenAIClient FineTuningJob
AuthClient
-> CreateEmbeddingRequest -> OpenAIClient CreateEmbeddingResponse
AuthClient
-> CreateCompletionRequest -> OpenAIClient CreateCompletionResponse
AuthClient
-> CreateChatCompletionRequest
-> OpenAIClient CreateChatCompletionResponse
AuthClient
-> CreateAssistantRequest -> OpenAIClient AssistantObject
AuthClient
-> FormCreateImageVariation -> OpenAIClient ImagesResponse
AuthClient -> FormCreateImageEdit -> OpenAIClient ImagesResponse
AuthClient -> FormCreateFile -> OpenAIClient OpenAIFile
AuthClient
-> FormCreateTranslation
-> OpenAIClient CreateTranslation200Response
AuthClient
-> FormCreateTranscription
-> OpenAIClient CreateTranscription200Response
$sel:cancelRun:OpenAIBackend :: AuthClient -> Text -> Text -> OpenAIClient RunObject
$sel:createAssistant:OpenAIBackend :: AuthClient
-> CreateAssistantRequest -> OpenAIClient AssistantObject
$sel:createAssistantFile:OpenAIBackend :: AuthClient
-> Text
-> CreateAssistantFileRequest
-> OpenAIClient AssistantFileObject
$sel:createMessage:OpenAIBackend :: AuthClient
-> Text -> CreateMessageRequest -> OpenAIClient MessageObject
$sel:createRun:OpenAIBackend :: AuthClient -> Text -> CreateRunRequest -> OpenAIClient RunObject
$sel:createThread:OpenAIBackend :: AuthClient -> CreateThreadRequest -> OpenAIClient ThreadObject
$sel:createThreadAndRun:OpenAIBackend :: AuthClient -> CreateThreadAndRunRequest -> OpenAIClient RunObject
$sel:deleteAssistant:OpenAIBackend :: AuthClient -> Text -> OpenAIClient DeleteAssistantResponse
$sel:deleteAssistantFile:OpenAIBackend :: AuthClient
-> Text -> Text -> OpenAIClient DeleteAssistantFileResponse
$sel:deleteThread:OpenAIBackend :: AuthClient -> Text -> OpenAIClient DeleteThreadResponse
$sel:getAssistant:OpenAIBackend :: AuthClient -> Text -> OpenAIClient AssistantObject
$sel:getAssistantFile:OpenAIBackend :: AuthClient -> Text -> Text -> OpenAIClient AssistantFileObject
$sel:getMessage:OpenAIBackend :: AuthClient -> Text -> Text -> OpenAIClient MessageObject
$sel:getMessageFile:OpenAIBackend :: AuthClient
-> Text -> Text -> Text -> OpenAIClient MessageFileObject
$sel:getRun:OpenAIBackend :: AuthClient -> Text -> Text -> OpenAIClient RunObject
$sel:getRunStep:OpenAIBackend :: AuthClient -> Text -> Text -> Text -> OpenAIClient RunStepObject
$sel:getThread:OpenAIBackend :: AuthClient -> Text -> OpenAIClient ThreadObject
$sel:listAssistantFiles:OpenAIBackend :: AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantFilesResponse
$sel:listAssistants:OpenAIBackend :: AuthClient
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantsResponse
$sel:listMessageFiles:OpenAIBackend :: AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessageFilesResponse
$sel:listMessages:OpenAIBackend :: AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessagesResponse
$sel:listRunSteps:OpenAIBackend :: AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunStepsResponse
$sel:listRuns:OpenAIBackend :: AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunsResponse
$sel:modifyAssistant:OpenAIBackend :: AuthClient
-> Text -> ModifyAssistantRequest -> OpenAIClient AssistantObject
$sel:modifyMessage:OpenAIBackend :: AuthClient
-> Text
-> Text
-> ModifyMessageRequest
-> OpenAIClient MessageObject
$sel:modifyRun:OpenAIBackend :: AuthClient
-> Text -> Text -> ModifyRunRequest -> OpenAIClient RunObject
$sel:modifyThread:OpenAIBackend :: AuthClient
-> Text -> ModifyThreadRequest -> OpenAIClient ThreadObject
$sel:submitToolOuputsToRun:OpenAIBackend :: AuthClient
-> Text
-> Text
-> SubmitToolOutputsRunRequest
-> OpenAIClient RunObject
$sel:createSpeech:OpenAIBackend :: AuthClient -> CreateSpeechRequest -> OpenAIClient ByteString
$sel:createTranscription:OpenAIBackend :: AuthClient
-> FormCreateTranscription
-> OpenAIClient CreateTranscription200Response
$sel:createTranslation:OpenAIBackend :: AuthClient
-> FormCreateTranslation
-> OpenAIClient CreateTranslation200Response
$sel:createChatCompletion:OpenAIBackend :: AuthClient
-> CreateChatCompletionRequest
-> OpenAIClient CreateChatCompletionResponse
$sel:createCompletion:OpenAIBackend :: AuthClient
-> CreateCompletionRequest -> OpenAIClient CreateCompletionResponse
$sel:createEmbedding:OpenAIBackend :: AuthClient
-> CreateEmbeddingRequest -> OpenAIClient CreateEmbeddingResponse
$sel:createFile:OpenAIBackend :: AuthClient -> FormCreateFile -> OpenAIClient OpenAIFile
$sel:deleteFile:OpenAIBackend :: AuthClient -> Text -> OpenAIClient DeleteFileResponse
$sel:downloadFile:OpenAIBackend :: AuthClient -> Text -> OpenAIClient Text
$sel:listFiles:OpenAIBackend :: AuthClient -> Maybe Text -> OpenAIClient ListFilesResponse
$sel:retrieveFile:OpenAIBackend :: AuthClient -> Text -> OpenAIClient OpenAIFile
$sel:cancelFineTuningJob:OpenAIBackend :: AuthClient -> Text -> OpenAIClient FineTuningJob
$sel:createFineTuningJob:OpenAIBackend :: AuthClient
-> CreateFineTuningJobRequest -> OpenAIClient FineTuningJob
$sel:listFineTuningEvents:OpenAIBackend :: AuthClient
-> Text
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListFineTuningJobEventsResponse
$sel:listPaginatedFineTuningJobs:OpenAIBackend :: AuthClient
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListPaginatedFineTuningJobsResponse
$sel:retrieveFineTuningJob:OpenAIBackend :: AuthClient -> Text -> OpenAIClient FineTuningJob
$sel:createImage:OpenAIBackend :: AuthClient -> CreateImageRequest -> OpenAIClient ImagesResponse
$sel:createImageEdit:OpenAIBackend :: AuthClient -> FormCreateImageEdit -> OpenAIClient ImagesResponse
$sel:createImageVariation:OpenAIBackend :: AuthClient
-> FormCreateImageVariation -> OpenAIClient ImagesResponse
$sel:deleteModel:OpenAIBackend :: AuthClient -> Text -> OpenAIClient DeleteModelResponse
$sel:listModels:OpenAIBackend :: AuthClient -> OpenAIClient ListModelsResponse
$sel:retrieveModel:OpenAIBackend :: AuthClient -> Text -> OpenAIClient Model
$sel:createModeration:OpenAIBackend :: AuthClient
-> CreateModerationRequest -> OpenAIClient CreateModerationResponse
cancelRun :: AuthClient -> Text -> Text -> OpenAIClient RunObject
createAssistant :: AuthClient
-> CreateAssistantRequest -> OpenAIClient AssistantObject
createAssistantFile :: AuthClient
-> Text
-> CreateAssistantFileRequest
-> OpenAIClient AssistantFileObject
createMessage :: AuthClient
-> Text -> CreateMessageRequest -> OpenAIClient MessageObject
createRun :: AuthClient -> Text -> CreateRunRequest -> OpenAIClient RunObject
createThread :: AuthClient -> CreateThreadRequest -> OpenAIClient ThreadObject
createThreadAndRun :: AuthClient -> CreateThreadAndRunRequest -> OpenAIClient RunObject
deleteAssistant :: AuthClient -> Text -> OpenAIClient DeleteAssistantResponse
deleteAssistantFile :: AuthClient
-> Text -> Text -> OpenAIClient DeleteAssistantFileResponse
deleteThread :: AuthClient -> Text -> OpenAIClient DeleteThreadResponse
getAssistant :: AuthClient -> Text -> OpenAIClient AssistantObject
getAssistantFile :: AuthClient -> Text -> Text -> OpenAIClient AssistantFileObject
getMessage :: AuthClient -> Text -> Text -> OpenAIClient MessageObject
getMessageFile :: AuthClient
-> Text -> Text -> Text -> OpenAIClient MessageFileObject
getRun :: AuthClient -> Text -> Text -> OpenAIClient RunObject
getRunStep :: AuthClient -> Text -> Text -> Text -> OpenAIClient RunStepObject
getThread :: AuthClient -> Text -> OpenAIClient ThreadObject
listAssistantFiles :: AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantFilesResponse
listAssistants :: AuthClient
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantsResponse
listMessageFiles :: AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessageFilesResponse
listMessages :: AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessagesResponse
listRunSteps :: AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunStepsResponse
listRuns :: AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunsResponse
modifyAssistant :: AuthClient
-> Text -> ModifyAssistantRequest -> OpenAIClient AssistantObject
modifyMessage :: AuthClient
-> Text
-> Text
-> ModifyMessageRequest
-> OpenAIClient MessageObject
modifyRun :: AuthClient
-> Text -> Text -> ModifyRunRequest -> OpenAIClient RunObject
modifyThread :: AuthClient
-> Text -> ModifyThreadRequest -> OpenAIClient ThreadObject
submitToolOuputsToRun :: AuthClient
-> Text
-> Text
-> SubmitToolOutputsRunRequest
-> OpenAIClient RunObject
createSpeech :: AuthClient -> CreateSpeechRequest -> OpenAIClient ByteString
createTranscription :: AuthClient
-> FormCreateTranscription
-> OpenAIClient CreateTranscription200Response
createTranslation :: AuthClient
-> FormCreateTranslation
-> OpenAIClient CreateTranslation200Response
createChatCompletion :: AuthClient
-> CreateChatCompletionRequest
-> OpenAIClient CreateChatCompletionResponse
createCompletion :: AuthClient
-> CreateCompletionRequest -> OpenAIClient CreateCompletionResponse
createEmbedding :: AuthClient
-> CreateEmbeddingRequest -> OpenAIClient CreateEmbeddingResponse
createFile :: AuthClient -> FormCreateFile -> OpenAIClient OpenAIFile
deleteFile :: AuthClient -> Text -> OpenAIClient DeleteFileResponse
downloadFile :: AuthClient -> Text -> OpenAIClient Text
listFiles :: AuthClient -> Maybe Text -> OpenAIClient ListFilesResponse
retrieveFile :: AuthClient -> Text -> OpenAIClient OpenAIFile
cancelFineTuningJob :: AuthClient -> Text -> OpenAIClient FineTuningJob
createFineTuningJob :: AuthClient
-> CreateFineTuningJobRequest -> OpenAIClient FineTuningJob
listFineTuningEvents :: AuthClient
-> Text
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListFineTuningJobEventsResponse
listPaginatedFineTuningJobs :: AuthClient
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListPaginatedFineTuningJobsResponse
retrieveFineTuningJob :: AuthClient -> Text -> OpenAIClient FineTuningJob
createImage :: AuthClient -> CreateImageRequest -> OpenAIClient ImagesResponse
createImageEdit :: AuthClient -> FormCreateImageEdit -> OpenAIClient ImagesResponse
createImageVariation :: AuthClient
-> FormCreateImageVariation -> OpenAIClient ImagesResponse
deleteModel :: AuthClient -> Text -> OpenAIClient DeleteModelResponse
listModels :: AuthClient -> OpenAIClient ListModelsResponse
retrieveModel :: AuthClient -> Text -> OpenAIClient Model
createModeration :: AuthClient
-> CreateModerationRequest -> OpenAIClient CreateModerationResponse
..}
where
(((AuthClient -> Text -> Text -> ClientM RunObject)
-> AuthClient -> Text -> Text -> OpenAIClient RunObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> Text -> OpenAIClient RunObject
cancelRun) :<|>
((AuthClient -> CreateAssistantRequest -> ClientM AssistantObject)
-> AuthClient
-> CreateAssistantRequest
-> OpenAIClient AssistantObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> CreateAssistantRequest -> OpenAIClient AssistantObject
createAssistant) :<|>
((AuthClient
-> Text
-> CreateAssistantFileRequest
-> ClientM AssistantFileObject)
-> AuthClient
-> Text
-> CreateAssistantFileRequest
-> OpenAIClient AssistantFileObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> CreateAssistantFileRequest
-> OpenAIClient AssistantFileObject
createAssistantFile) :<|>
((AuthClient
-> Text -> CreateMessageRequest -> ClientM MessageObject)
-> AuthClient
-> Text
-> CreateMessageRequest
-> OpenAIClient MessageObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text -> CreateMessageRequest -> OpenAIClient MessageObject
createMessage) :<|>
((AuthClient -> Text -> CreateRunRequest -> ClientM RunObject)
-> AuthClient -> Text -> CreateRunRequest -> OpenAIClient RunObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> CreateRunRequest -> OpenAIClient RunObject
createRun) :<|>
((AuthClient -> CreateThreadRequest -> ClientM ThreadObject)
-> AuthClient -> CreateThreadRequest -> OpenAIClient ThreadObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> CreateThreadRequest -> OpenAIClient ThreadObject
createThread) :<|>
((AuthClient -> CreateThreadAndRunRequest -> ClientM RunObject)
-> AuthClient
-> CreateThreadAndRunRequest
-> OpenAIClient RunObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> CreateThreadAndRunRequest -> OpenAIClient RunObject
createThreadAndRun) :<|>
((AuthClient -> Text -> ClientM DeleteAssistantResponse)
-> AuthClient -> Text -> OpenAIClient DeleteAssistantResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient DeleteAssistantResponse
deleteAssistant) :<|>
((AuthClient -> Text -> Text -> ClientM DeleteAssistantFileResponse)
-> AuthClient
-> Text
-> Text
-> OpenAIClient DeleteAssistantFileResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text -> Text -> OpenAIClient DeleteAssistantFileResponse
deleteAssistantFile) :<|>
((AuthClient -> Text -> ClientM DeleteThreadResponse)
-> AuthClient -> Text -> OpenAIClient DeleteThreadResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient DeleteThreadResponse
deleteThread) :<|>
((AuthClient -> Text -> ClientM AssistantObject)
-> AuthClient -> Text -> OpenAIClient AssistantObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient AssistantObject
getAssistant) :<|>
((AuthClient -> Text -> Text -> ClientM AssistantFileObject)
-> AuthClient -> Text -> Text -> OpenAIClient AssistantFileObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> Text -> OpenAIClient AssistantFileObject
getAssistantFile) :<|>
((AuthClient -> Text -> Text -> ClientM MessageObject)
-> AuthClient -> Text -> Text -> OpenAIClient MessageObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> Text -> OpenAIClient MessageObject
getMessage) :<|>
((AuthClient -> Text -> Text -> Text -> ClientM MessageFileObject)
-> AuthClient
-> Text
-> Text
-> Text
-> OpenAIClient MessageFileObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text -> Text -> Text -> OpenAIClient MessageFileObject
getMessageFile) :<|>
((AuthClient -> Text -> Text -> ClientM RunObject)
-> AuthClient -> Text -> Text -> OpenAIClient RunObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> Text -> OpenAIClient RunObject
getRun) :<|>
((AuthClient -> Text -> Text -> Text -> ClientM RunStepObject)
-> AuthClient -> Text -> Text -> Text -> OpenAIClient RunStepObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> Text -> Text -> OpenAIClient RunStepObject
getRunStep) :<|>
((AuthClient -> Text -> ClientM ThreadObject)
-> AuthClient -> Text -> OpenAIClient ThreadObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient ThreadObject
getThread) :<|>
((AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> ClientM ListAssistantFilesResponse)
-> AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantFilesResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantFilesResponse
listAssistantFiles) :<|>
((AuthClient
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> ClientM ListAssistantsResponse)
-> AuthClient
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantsResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListAssistantsResponse
listAssistants) :<|>
((AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> ClientM ListMessageFilesResponse)
-> AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessageFilesResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessageFilesResponse
listMessageFiles) :<|>
((AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> ClientM ListMessagesResponse)
-> AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessagesResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListMessagesResponse
listMessages) :<|>
((AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> ClientM ListRunStepsResponse)
-> AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunStepsResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunStepsResponse
listRunSteps) :<|>
((AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> ClientM ListRunsResponse)
-> AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunsResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> OpenAIClient ListRunsResponse
listRuns) :<|>
((AuthClient
-> Text -> ModifyAssistantRequest -> ClientM AssistantObject)
-> AuthClient
-> Text
-> ModifyAssistantRequest
-> OpenAIClient AssistantObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text -> ModifyAssistantRequest -> OpenAIClient AssistantObject
modifyAssistant) :<|>
((AuthClient
-> Text -> Text -> ModifyMessageRequest -> ClientM MessageObject)
-> AuthClient
-> Text
-> Text
-> ModifyMessageRequest
-> OpenAIClient MessageObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Text
-> ModifyMessageRequest
-> OpenAIClient MessageObject
modifyMessage) :<|>
((AuthClient
-> Text -> Text -> ModifyRunRequest -> ClientM RunObject)
-> AuthClient
-> Text
-> Text
-> ModifyRunRequest
-> OpenAIClient RunObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text -> Text -> ModifyRunRequest -> OpenAIClient RunObject
modifyRun) :<|>
((AuthClient -> Text -> ModifyThreadRequest -> ClientM ThreadObject)
-> AuthClient
-> Text
-> ModifyThreadRequest
-> OpenAIClient ThreadObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text -> ModifyThreadRequest -> OpenAIClient ThreadObject
modifyThread) :<|>
((AuthClient
-> Text
-> Text
-> SubmitToolOutputsRunRequest
-> ClientM RunObject)
-> AuthClient
-> Text
-> Text
-> SubmitToolOutputsRunRequest
-> OpenAIClient RunObject
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Text
-> SubmitToolOutputsRunRequest
-> OpenAIClient RunObject
submitToolOuputsToRun) :<|>
((AuthClient -> CreateSpeechRequest -> ClientM ByteString)
-> AuthClient -> CreateSpeechRequest -> OpenAIClient ByteString
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> CreateSpeechRequest -> OpenAIClient ByteString
createSpeech) :<|>
((AuthClient
-> FormCreateTranscription
-> ClientM CreateTranscription200Response)
-> AuthClient
-> FormCreateTranscription
-> OpenAIClient CreateTranscription200Response
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> FormCreateTranscription
-> OpenAIClient CreateTranscription200Response
createTranscription) :<|>
((AuthClient
-> FormCreateTranslation -> ClientM CreateTranslation200Response)
-> AuthClient
-> FormCreateTranslation
-> OpenAIClient CreateTranslation200Response
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> FormCreateTranslation
-> OpenAIClient CreateTranslation200Response
createTranslation) :<|>
((AuthClient
-> CreateChatCompletionRequest
-> ClientM CreateChatCompletionResponse)
-> AuthClient
-> CreateChatCompletionRequest
-> OpenAIClient CreateChatCompletionResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> CreateChatCompletionRequest
-> OpenAIClient CreateChatCompletionResponse
createChatCompletion) :<|>
((AuthClient
-> CreateCompletionRequest -> ClientM CreateCompletionResponse)
-> AuthClient
-> CreateCompletionRequest
-> OpenAIClient CreateCompletionResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> CreateCompletionRequest -> OpenAIClient CreateCompletionResponse
createCompletion) :<|>
((AuthClient
-> CreateEmbeddingRequest -> ClientM CreateEmbeddingResponse)
-> AuthClient
-> CreateEmbeddingRequest
-> OpenAIClient CreateEmbeddingResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> CreateEmbeddingRequest -> OpenAIClient CreateEmbeddingResponse
createEmbedding) :<|>
((AuthClient -> FormCreateFile -> ClientM OpenAIFile)
-> AuthClient -> FormCreateFile -> OpenAIClient OpenAIFile
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> FormCreateFile -> OpenAIClient OpenAIFile
createFile) :<|>
((AuthClient -> Text -> ClientM DeleteFileResponse)
-> AuthClient -> Text -> OpenAIClient DeleteFileResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient DeleteFileResponse
deleteFile) :<|>
((AuthClient -> Text -> ClientM Text)
-> AuthClient -> Text -> OpenAIClient Text
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient Text
downloadFile) :<|>
((AuthClient -> Maybe Text -> ClientM ListFilesResponse)
-> AuthClient -> Maybe Text -> OpenAIClient ListFilesResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Maybe Text -> OpenAIClient ListFilesResponse
listFiles) :<|>
((AuthClient -> Text -> ClientM OpenAIFile)
-> AuthClient -> Text -> OpenAIClient OpenAIFile
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient OpenAIFile
retrieveFile) :<|>
((AuthClient -> Text -> ClientM FineTuningJob)
-> AuthClient -> Text -> OpenAIClient FineTuningJob
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient FineTuningJob
cancelFineTuningJob) :<|>
((AuthClient -> CreateFineTuningJobRequest -> ClientM FineTuningJob)
-> AuthClient
-> CreateFineTuningJobRequest
-> OpenAIClient FineTuningJob
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> CreateFineTuningJobRequest -> OpenAIClient FineTuningJob
createFineTuningJob) :<|>
((AuthClient
-> Text
-> Maybe Text
-> Maybe Int
-> ClientM ListFineTuningJobEventsResponse)
-> AuthClient
-> Text
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListFineTuningJobEventsResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Text
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListFineTuningJobEventsResponse
listFineTuningEvents) :<|>
((AuthClient
-> Maybe Text
-> Maybe Int
-> ClientM ListPaginatedFineTuningJobsResponse)
-> AuthClient
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListPaginatedFineTuningJobsResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> Maybe Text
-> Maybe Int
-> OpenAIClient ListPaginatedFineTuningJobsResponse
listPaginatedFineTuningJobs) :<|>
((AuthClient -> Text -> ClientM FineTuningJob)
-> AuthClient -> Text -> OpenAIClient FineTuningJob
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient FineTuningJob
retrieveFineTuningJob) :<|>
((AuthClient -> CreateImageRequest -> ClientM ImagesResponse)
-> AuthClient -> CreateImageRequest -> OpenAIClient ImagesResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> CreateImageRequest -> OpenAIClient ImagesResponse
createImage) :<|>
((AuthClient -> FormCreateImageEdit -> ClientM ImagesResponse)
-> AuthClient -> FormCreateImageEdit -> OpenAIClient ImagesResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> FormCreateImageEdit -> OpenAIClient ImagesResponse
createImageEdit) :<|>
((AuthClient -> FormCreateImageVariation -> ClientM ImagesResponse)
-> AuthClient
-> FormCreateImageVariation
-> OpenAIClient ImagesResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> FormCreateImageVariation -> OpenAIClient ImagesResponse
createImageVariation) :<|>
((AuthClient -> Text -> ClientM DeleteModelResponse)
-> AuthClient -> Text -> OpenAIClient DeleteModelResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient DeleteModelResponse
deleteModel) :<|>
((AuthClient -> ClientM ListModelsResponse)
-> AuthClient -> OpenAIClient ListModelsResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> OpenAIClient ListModelsResponse
listModels) :<|>
((AuthClient -> Text -> ClientM Model)
-> AuthClient -> Text -> OpenAIClient Model
forall a b. Coercible a b => a -> b
coerce -> AuthClient -> Text -> OpenAIClient Model
retrieveModel) :<|>
((AuthClient
-> CreateModerationRequest -> ClientM CreateModerationResponse)
-> AuthClient
-> CreateModerationRequest
-> OpenAIClient CreateModerationResponse
forall a b. Coercible a b => a -> b
coerce -> AuthClient
-> CreateModerationRequest -> OpenAIClient CreateModerationResponse
createModeration) :<|>
ByteString -> ClientM Response
_) = Proxy OpenAIAPI -> Client ClientM OpenAIAPI
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy OpenAIAPI
forall {k} (t :: k). Proxy t
Proxy :: Proxy OpenAIAPI)
runOpenAIClient :: Config -> OpenAIClient a -> ExceptT ClientError IO a
runOpenAIClient :: forall a. Config -> OpenAIClient a -> ExceptT ClientError IO a
runOpenAIClient Config
clientConfig OpenAIClient a
cl = do
Manager
manager <- IO Manager -> ExceptT ClientError IO Manager
forall a. IO a -> ExceptT ClientError IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Manager -> ExceptT ClientError IO Manager)
-> IO Manager -> ExceptT ClientError IO Manager
forall a b. (a -> b) -> a -> b
$ ManagerSettings -> IO Manager
newManager ManagerSettings
tlsManagerSettings
Manager -> Config -> OpenAIClient a -> ExceptT ClientError IO a
forall a.
Manager -> Config -> OpenAIClient a -> ExceptT ClientError IO a
runOpenAIClientWithManager Manager
manager Config
clientConfig OpenAIClient a
cl
runOpenAIClientWithManager :: Manager -> Config -> OpenAIClient a -> ExceptT ClientError IO a
runOpenAIClientWithManager :: forall a.
Manager -> Config -> OpenAIClient a -> ExceptT ClientError IO a
runOpenAIClientWithManager Manager
manager Config{FilePath
$sel:configUrl:Config :: Config -> FilePath
configUrl :: FilePath
..} OpenAIClient a
cl = do
BaseUrl
url <- FilePath -> ExceptT ClientError IO BaseUrl
forall (m :: * -> *). MonadThrow m => FilePath -> m BaseUrl
parseBaseUrl FilePath
configUrl
OpenAIClient a -> ClientEnv -> ExceptT ClientError IO a
forall a. OpenAIClient a -> ClientEnv -> ExceptT ClientError IO a
runClient OpenAIClient a
cl (ClientEnv -> ExceptT ClientError IO a)
-> ClientEnv -> ExceptT ClientError IO a
forall a b. (a -> b) -> a -> b
$ Manager -> BaseUrl -> ClientEnv
mkClientEnv Manager
manager BaseUrl
url
callOpenAI
:: (MonadIO m, MonadThrow m)
=> ClientEnv -> OpenAIClient a -> m a
callOpenAI :: forall (m :: * -> *) a.
(MonadIO m, MonadThrow m) =>
ClientEnv -> OpenAIClient a -> m a
callOpenAI ClientEnv
env OpenAIClient a
f = do
Either ClientError a
res <- IO (Either ClientError a) -> m (Either ClientError a)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either ClientError a) -> m (Either ClientError a))
-> IO (Either ClientError a) -> m (Either ClientError a)
forall a b. (a -> b) -> a -> b
$ ExceptT ClientError IO a -> IO (Either ClientError a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT ClientError IO a -> IO (Either ClientError a))
-> ExceptT ClientError IO a -> IO (Either ClientError a)
forall a b. (a -> b) -> a -> b
$ OpenAIClient a -> ClientEnv -> ExceptT ClientError IO a
forall a. OpenAIClient a -> ClientEnv -> ExceptT ClientError IO a
runClient OpenAIClient a
f ClientEnv
env
case Either ClientError a
res of
Left ClientError
err -> OpenAIClientError -> m a
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (ClientError -> OpenAIClientError
OpenAIClientError ClientError
err)
Right a
response -> a -> m a
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
response
requestMiddlewareId :: Application -> Application
requestMiddlewareId :: Application -> Application
requestMiddlewareId Application
a = Application
a
runOpenAIServer
:: (MonadIO m, MonadThrow m)
=> Config -> OpenAIAuth -> OpenAIBackend AuthServer (ExceptT ServerError IO) -> m ()
runOpenAIServer :: forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
Config
-> OpenAIAuth
-> OpenAIBackend
(AuthServerData Protected) (ExceptT ServerError IO)
-> m ()
runOpenAIServer Config
config OpenAIAuth
auth OpenAIBackend (AuthServerData Protected) (ExceptT ServerError IO)
backend = Config
-> (Application -> Application)
-> OpenAIAuth
-> OpenAIBackend
(AuthServerData Protected) (ExceptT ServerError IO)
-> m ()
forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
Config
-> (Application -> Application)
-> OpenAIAuth
-> OpenAIBackend
(AuthServerData Protected) (ExceptT ServerError IO)
-> m ()
runOpenAIMiddlewareServer Config
config Application -> Application
requestMiddlewareId OpenAIAuth
auth OpenAIBackend (AuthServerData Protected) (ExceptT ServerError IO)
backend
runOpenAIMiddlewareServer
:: (MonadIO m, MonadThrow m)
=> Config -> Middleware -> OpenAIAuth -> OpenAIBackend AuthServer (ExceptT ServerError IO) -> m ()
runOpenAIMiddlewareServer :: forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
Config
-> (Application -> Application)
-> OpenAIAuth
-> OpenAIBackend
(AuthServerData Protected) (ExceptT ServerError IO)
-> m ()
runOpenAIMiddlewareServer Config{FilePath
$sel:configUrl:Config :: Config -> FilePath
configUrl :: FilePath
..} Application -> Application
middleware OpenAIAuth
auth OpenAIBackend (AuthServerData Protected) (ExceptT ServerError IO)
backend = do
BaseUrl
url <- FilePath -> m BaseUrl
forall (m :: * -> *). MonadThrow m => FilePath -> m BaseUrl
parseBaseUrl FilePath
configUrl
let warpSettings :: Settings
warpSettings = Settings
Warp.defaultSettings
Settings -> (Settings -> Settings) -> Settings
forall a b. a -> (a -> b) -> b
& Int -> Settings -> Settings
Warp.setPort (BaseUrl -> Int
baseUrlPort BaseUrl
url)
Settings -> (Settings -> Settings) -> Settings
forall a b. a -> (a -> b) -> b
& HostPreference -> Settings -> Settings
Warp.setHost (FilePath -> HostPreference
forall a. IsString a => FilePath -> a
fromString (FilePath -> HostPreference) -> FilePath -> HostPreference
forall a b. (a -> b) -> a -> b
$ BaseUrl -> FilePath
baseUrlHost BaseUrl
url)
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Settings -> Application -> IO ()
Warp.runSettings Settings
warpSettings (Application -> IO ()) -> Application -> IO ()
forall a b. (a -> b) -> a -> b
$ Application -> Application
middleware (Application -> Application) -> Application -> Application
forall a b. (a -> b) -> a -> b
$ OpenAIAuth
-> OpenAIBackend
(AuthServerData Protected) (ExceptT ServerError IO)
-> Application
serverWaiApplicationOpenAI OpenAIAuth
auth OpenAIBackend (AuthServerData Protected) (ExceptT ServerError IO)
backend
serverWaiApplicationOpenAI :: OpenAIAuth -> OpenAIBackend AuthServer (ExceptT ServerError IO) -> Application
serverWaiApplicationOpenAI :: OpenAIAuth
-> OpenAIBackend
(AuthServerData Protected) (ExceptT ServerError IO)
-> Application
serverWaiApplicationOpenAI OpenAIAuth
auth OpenAIBackend (AuthServerData Protected) (ExceptT ServerError IO)
backend = Proxy OpenAIAPI
-> Context '[AuthHandler Request (AuthServerData Protected)]
-> (forall x. Handler x -> Handler x)
-> ServerT OpenAIAPI Handler
-> Application
forall api (context :: [*]) (m :: * -> *).
(HasServer api context, ServerContext context) =>
Proxy api
-> Context context
-> (forall x. m x -> Handler x)
-> ServerT api m
-> Application
serveWithContextT (Proxy OpenAIAPI
forall {k} (t :: k). Proxy t
Proxy :: Proxy OpenAIAPI) Context '[AuthHandler Request (AuthServerData Protected)]
context Handler x -> Handler x
forall a. a -> a
forall x. Handler x -> Handler x
id (OpenAIBackend (AuthServerData Protected) (ExceptT ServerError IO)
-> (AuthServerData Protected -> Text -> Text -> Handler RunObject)
:<|> ((AuthServerData Protected
-> CreateAssistantRequest -> Handler AssistantObject)
:<|> ((AuthServerData Protected
-> Text
-> CreateAssistantFileRequest
-> Handler AssistantFileObject)
:<|> ((AuthServerData Protected
-> Text -> CreateMessageRequest -> Handler MessageObject)
:<|> ((AuthServerData Protected
-> Text -> CreateRunRequest -> Handler RunObject)
:<|> ((AuthServerData Protected
-> CreateThreadRequest -> Handler ThreadObject)
:<|> ((AuthServerData Protected
-> CreateThreadAndRunRequest -> Handler RunObject)
:<|> ((AuthServerData Protected
-> Text -> Handler DeleteAssistantResponse)
:<|> ((AuthServerData Protected
-> Text
-> Text
-> Handler DeleteAssistantFileResponse)
:<|> ((AuthServerData Protected
-> Text -> Handler DeleteThreadResponse)
:<|> ((AuthServerData Protected
-> Text -> Handler AssistantObject)
:<|> ((AuthServerData Protected
-> Text
-> Text
-> Handler
AssistantFileObject)
:<|> ((AuthServerData Protected
-> Text
-> Text
-> Handler
MessageObject)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> Text
-> Handler
MessageFileObject)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> Handler
RunObject)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> Text
-> Handler
RunStepObject)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
ThreadObject)
:<|> ((AuthServerData
Protected
-> Text
-> Maybe
Int
-> Maybe
Text
-> Maybe
Text
-> Maybe
Text
-> Handler
ListAssistantFilesResponse)
:<|> ((AuthServerData
Protected
-> Maybe
Int
-> Maybe
Text
-> Maybe
Text
-> Maybe
Text
-> Handler
ListAssistantsResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> Maybe
Int
-> Maybe
Text
-> Maybe
Text
-> Maybe
Text
-> Handler
ListMessageFilesResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Maybe
Int
-> Maybe
Text
-> Maybe
Text
-> Maybe
Text
-> Handler
ListMessagesResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> Maybe
Int
-> Maybe
Text
-> Maybe
Text
-> Maybe
Text
-> Handler
ListRunStepsResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Maybe
Int
-> Maybe
Text
-> Maybe
Text
-> Maybe
Text
-> Handler
ListRunsResponse)
:<|> ((AuthServerData
Protected
-> Text
-> ModifyAssistantRequest
-> Handler
AssistantObject)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> ModifyMessageRequest
-> Handler
MessageObject)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> ModifyRunRequest
-> Handler
RunObject)
:<|> ((AuthServerData
Protected
-> Text
-> ModifyThreadRequest
-> Handler
ThreadObject)
:<|> ((AuthServerData
Protected
-> Text
-> Text
-> SubmitToolOutputsRunRequest
-> Handler
RunObject)
:<|> ((AuthServerData
Protected
-> CreateSpeechRequest
-> Handler
ByteString)
:<|> ((AuthServerData
Protected
-> FormCreateTranscription
-> Handler
CreateTranscription200Response)
:<|> ((AuthServerData
Protected
-> FormCreateTranslation
-> Handler
CreateTranslation200Response)
:<|> ((AuthServerData
Protected
-> CreateChatCompletionRequest
-> Handler
CreateChatCompletionResponse)
:<|> ((AuthServerData
Protected
-> CreateCompletionRequest
-> Handler
CreateCompletionResponse)
:<|> ((AuthServerData
Protected
-> CreateEmbeddingRequest
-> Handler
CreateEmbeddingResponse)
:<|> ((AuthServerData
Protected
-> FormCreateFile
-> Handler
OpenAIFile)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
DeleteFileResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
Text)
:<|> ((AuthServerData
Protected
-> Maybe
Text
-> Handler
ListFilesResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
OpenAIFile)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
FineTuningJob)
:<|> ((AuthServerData
Protected
-> CreateFineTuningJobRequest
-> Handler
FineTuningJob)
:<|> ((AuthServerData
Protected
-> Text
-> Maybe
Text
-> Maybe
Int
-> Handler
ListFineTuningJobEventsResponse)
:<|> ((AuthServerData
Protected
-> Maybe
Text
-> Maybe
Int
-> Handler
ListPaginatedFineTuningJobsResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
FineTuningJob)
:<|> ((AuthServerData
Protected
-> CreateImageRequest
-> Handler
ImagesResponse)
:<|> ((AuthServerData
Protected
-> FormCreateImageEdit
-> Handler
ImagesResponse)
:<|> ((AuthServerData
Protected
-> FormCreateImageVariation
-> Handler
ImagesResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
DeleteModelResponse)
:<|> ((AuthServerData
Protected
-> Handler
ListModelsResponse)
:<|> ((AuthServerData
Protected
-> Text
-> Handler
Model)
:<|> ((AuthServerData
Protected
-> CreateModerationRequest
-> Handler
CreateModerationResponse)
:<|> Tagged
Handler
Application))))))))))))))))))))))))))))))))))))))))))))))))))
forall {a} {a} {m :: * -> *} {a} {a} {a} {a} {a} {a} {a} {a} {a}
{a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a}
{a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a} {a}
{a} {a} {a} {a} {a} {a} {a} {m :: * -> *}.
(Coercible a (a -> Text -> m Model),
Coercible a (a -> Text -> m DeleteModelResponse),
Coercible a (a -> FormCreateImageEdit -> m ImagesResponse),
Coercible a (a -> Text -> m FineTuningJob),
Coercible
a
(a
-> Text
-> Maybe Text
-> Maybe Int
-> m ListFineTuningJobEventsResponse),
Coercible a (a -> Text -> m FineTuningJob),
Coercible a (a -> Maybe Text -> m ListFilesResponse),
Coercible a (a -> Text -> m DeleteFileResponse),
Coercible
a (a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse),
Coercible
a
(a
-> CreateChatCompletionRequest -> m CreateChatCompletionResponse),
Coercible
a
(a -> FormCreateTranscription -> m CreateTranscription200Response),
Coercible
a
(a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject),
Coercible a (a -> Text -> Text -> ModifyRunRequest -> m RunObject),
Coercible
a (a -> Text -> ModifyAssistantRequest -> m AssistantObject),
Coercible
a
(a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunStepsResponse),
Coercible
a
(a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessageFilesResponse),
Coercible
a
(a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantFilesResponse),
Coercible a (a -> Text -> Text -> Text -> m RunStepObject),
Coercible a (a -> Text -> Text -> Text -> m MessageFileObject),
Coercible a (a -> Text -> Text -> m AssistantFileObject),
Coercible a (a -> Text -> m DeleteThreadResponse),
Coercible a (a -> Text -> m DeleteAssistantResponse),
Coercible a (a -> CreateThreadRequest -> m ThreadObject),
Coercible a (a -> Text -> CreateMessageRequest -> m MessageObject),
Coercible a (a -> CreateAssistantRequest -> m AssistantObject),
Coercible a (a -> Text -> Text -> m RunObject),
Coercible
a
(a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject),
Coercible a (a -> Text -> CreateRunRequest -> m RunObject),
Coercible a (a -> CreateThreadAndRunRequest -> m RunObject),
Coercible a (a -> Text -> Text -> m DeleteAssistantFileResponse),
Coercible a (a -> Text -> m AssistantObject),
Coercible a (a -> Text -> Text -> m MessageObject),
Coercible a (a -> Text -> Text -> m RunObject),
Coercible a (a -> Text -> m ThreadObject),
Coercible
a
(a
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantsResponse),
Coercible
a
(a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessagesResponse),
Coercible
a
(a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunsResponse),
Coercible
a (a -> Text -> Text -> ModifyMessageRequest -> m MessageObject),
Coercible a (a -> Text -> ModifyThreadRequest -> m ThreadObject),
Coercible a (a -> CreateSpeechRequest -> m ByteString),
Coercible
a (a -> FormCreateTranslation -> m CreateTranslation200Response),
Coercible
a (a -> CreateCompletionRequest -> m CreateCompletionResponse),
Coercible a (a -> FormCreateFile -> m OpenAIFile),
Coercible a (a -> Text -> m Text),
Coercible a (a -> Text -> m OpenAIFile),
Coercible a (a -> CreateFineTuningJobRequest -> m FineTuningJob),
Coercible
a
(a
-> Maybe Text
-> Maybe Int
-> m ListPaginatedFineTuningJobsResponse),
Coercible a (a -> CreateImageRequest -> m ImagesResponse),
Coercible a (a -> FormCreateImageVariation -> m ImagesResponse),
Coercible a (a -> m ListModelsResponse),
Coercible
a (a -> CreateModerationRequest -> m CreateModerationResponse)) =>
OpenAIBackend a m
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))))))
serverFromBackend OpenAIBackend (AuthServerData Protected) (ExceptT ServerError IO)
backend)
where
context :: Context '[AuthHandler Request (AuthServerData Protected)]
context = OpenAIAuth
-> Context '[AuthHandler Request (AuthServerData Protected)]
serverContext OpenAIAuth
auth
serverFromBackend :: OpenAIBackend a m
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))))))
serverFromBackend OpenAIBackend{a -> m ListModelsResponse
a
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantsResponse
a -> Maybe Text -> m ListFilesResponse
a
-> Maybe Text -> Maybe Int -> m ListPaginatedFineTuningJobsResponse
a -> Text -> m Text
a -> Text -> m ThreadObject
a -> Text -> m OpenAIFile
a -> Text -> m Model
a -> Text -> m FineTuningJob
a -> Text -> m DeleteThreadResponse
a -> Text -> m DeleteModelResponse
a -> Text -> m DeleteFileResponse
a -> Text -> m DeleteAssistantResponse
a -> Text -> m AssistantObject
a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunsResponse
a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessagesResponse
a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantFilesResponse
a
-> Text
-> Maybe Text
-> Maybe Int
-> m ListFineTuningJobEventsResponse
a -> Text -> Text -> m RunObject
a -> Text -> Text -> m MessageObject
a -> Text -> Text -> m DeleteAssistantFileResponse
a -> Text -> Text -> m AssistantFileObject
a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunStepsResponse
a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessageFilesResponse
a -> Text -> Text -> Text -> m RunStepObject
a -> Text -> Text -> Text -> m MessageFileObject
a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject
a -> Text -> Text -> ModifyRunRequest -> m RunObject
a -> Text -> Text -> ModifyMessageRequest -> m MessageObject
a -> Text -> ModifyThreadRequest -> m ThreadObject
a -> Text -> ModifyAssistantRequest -> m AssistantObject
a -> Text -> CreateRunRequest -> m RunObject
a -> Text -> CreateMessageRequest -> m MessageObject
a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject
a -> CreateThreadRequest -> m ThreadObject
a -> CreateThreadAndRunRequest -> m RunObject
a -> CreateSpeechRequest -> m ByteString
a -> CreateModerationRequest -> m CreateModerationResponse
a -> CreateImageRequest -> m ImagesResponse
a -> CreateFineTuningJobRequest -> m FineTuningJob
a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse
a -> CreateCompletionRequest -> m CreateCompletionResponse
a -> CreateChatCompletionRequest -> m CreateChatCompletionResponse
a -> CreateAssistantRequest -> m AssistantObject
a -> FormCreateImageVariation -> m ImagesResponse
a -> FormCreateImageEdit -> m ImagesResponse
a -> FormCreateFile -> m OpenAIFile
a -> FormCreateTranslation -> m CreateTranslation200Response
a -> FormCreateTranscription -> m CreateTranscription200Response
$sel:cancelRun:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m RunObject
$sel:createAssistant:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateAssistantRequest -> m AssistantObject
$sel:createAssistantFile:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject
$sel:createMessage:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> CreateMessageRequest -> m MessageObject
$sel:createRun:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> CreateRunRequest -> m RunObject
$sel:createThread:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateThreadRequest -> m ThreadObject
$sel:createThreadAndRun:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateThreadAndRunRequest -> m RunObject
$sel:deleteAssistant:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteAssistantResponse
$sel:deleteAssistantFile:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> m DeleteAssistantFileResponse
$sel:deleteThread:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteThreadResponse
$sel:getAssistant:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m AssistantObject
$sel:getAssistantFile:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m AssistantFileObject
$sel:getMessage:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m MessageObject
$sel:getMessageFile:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> Text -> m MessageFileObject
$sel:getRun:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> m RunObject
$sel:getRunStep:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> Text -> Text -> m RunStepObject
$sel:getThread:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m ThreadObject
$sel:listAssistantFiles:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantFilesResponse
$sel:listAssistants:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantsResponse
$sel:listMessageFiles:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessageFilesResponse
$sel:listMessages:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessagesResponse
$sel:listRunSteps:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunStepsResponse
$sel:listRuns:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunsResponse
$sel:modifyAssistant:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> ModifyAssistantRequest -> m AssistantObject
$sel:modifyMessage:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> ModifyMessageRequest -> m MessageObject
$sel:modifyRun:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> ModifyRunRequest -> m RunObject
$sel:modifyThread:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> ModifyThreadRequest -> m ThreadObject
$sel:submitToolOuputsToRun:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject
$sel:createSpeech:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateSpeechRequest -> m ByteString
$sel:createTranscription:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> FormCreateTranscription -> m CreateTranscription200Response
$sel:createTranslation:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> FormCreateTranslation -> m CreateTranslation200Response
$sel:createChatCompletion:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> CreateChatCompletionRequest
-> m CreateChatCompletionResponse
$sel:createCompletion:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateCompletionRequest -> m CreateCompletionResponse
$sel:createEmbedding:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse
$sel:createFile:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> FormCreateFile -> m OpenAIFile
$sel:deleteFile:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteFileResponse
$sel:downloadFile:OpenAIBackend :: forall a (m :: * -> *). OpenAIBackend a m -> a -> Text -> m Text
$sel:listFiles:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Maybe Text -> m ListFilesResponse
$sel:retrieveFile:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m OpenAIFile
$sel:cancelFineTuningJob:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m FineTuningJob
$sel:createFineTuningJob:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateFineTuningJobRequest -> m FineTuningJob
$sel:listFineTuningEvents:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Text
-> Maybe Text
-> Maybe Int
-> m ListFineTuningJobEventsResponse
$sel:listPaginatedFineTuningJobs:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a
-> Maybe Text
-> Maybe Int
-> m ListPaginatedFineTuningJobsResponse
$sel:retrieveFineTuningJob:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m FineTuningJob
$sel:createImage:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> CreateImageRequest -> m ImagesResponse
$sel:createImageEdit:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> FormCreateImageEdit -> m ImagesResponse
$sel:createImageVariation:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> FormCreateImageVariation -> m ImagesResponse
$sel:deleteModel:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> Text -> m DeleteModelResponse
$sel:listModels:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m -> a -> m ListModelsResponse
$sel:retrieveModel:OpenAIBackend :: forall a (m :: * -> *). OpenAIBackend a m -> a -> Text -> m Model
$sel:createModeration:OpenAIBackend :: forall a (m :: * -> *).
OpenAIBackend a m
-> a -> CreateModerationRequest -> m CreateModerationResponse
cancelRun :: a -> Text -> Text -> m RunObject
createAssistant :: a -> CreateAssistantRequest -> m AssistantObject
createAssistantFile :: a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject
createMessage :: a -> Text -> CreateMessageRequest -> m MessageObject
createRun :: a -> Text -> CreateRunRequest -> m RunObject
createThread :: a -> CreateThreadRequest -> m ThreadObject
createThreadAndRun :: a -> CreateThreadAndRunRequest -> m RunObject
deleteAssistant :: a -> Text -> m DeleteAssistantResponse
deleteAssistantFile :: a -> Text -> Text -> m DeleteAssistantFileResponse
deleteThread :: a -> Text -> m DeleteThreadResponse
getAssistant :: a -> Text -> m AssistantObject
getAssistantFile :: a -> Text -> Text -> m AssistantFileObject
getMessage :: a -> Text -> Text -> m MessageObject
getMessageFile :: a -> Text -> Text -> Text -> m MessageFileObject
getRun :: a -> Text -> Text -> m RunObject
getRunStep :: a -> Text -> Text -> Text -> m RunStepObject
getThread :: a -> Text -> m ThreadObject
listAssistantFiles :: a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantFilesResponse
listAssistants :: a
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantsResponse
listMessageFiles :: a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessageFilesResponse
listMessages :: a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessagesResponse
listRunSteps :: a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunStepsResponse
listRuns :: a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunsResponse
modifyAssistant :: a -> Text -> ModifyAssistantRequest -> m AssistantObject
modifyMessage :: a -> Text -> Text -> ModifyMessageRequest -> m MessageObject
modifyRun :: a -> Text -> Text -> ModifyRunRequest -> m RunObject
modifyThread :: a -> Text -> ModifyThreadRequest -> m ThreadObject
submitToolOuputsToRun :: a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject
createSpeech :: a -> CreateSpeechRequest -> m ByteString
createTranscription :: a -> FormCreateTranscription -> m CreateTranscription200Response
createTranslation :: a -> FormCreateTranslation -> m CreateTranslation200Response
createChatCompletion :: a -> CreateChatCompletionRequest -> m CreateChatCompletionResponse
createCompletion :: a -> CreateCompletionRequest -> m CreateCompletionResponse
createEmbedding :: a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse
createFile :: a -> FormCreateFile -> m OpenAIFile
deleteFile :: a -> Text -> m DeleteFileResponse
downloadFile :: a -> Text -> m Text
listFiles :: a -> Maybe Text -> m ListFilesResponse
retrieveFile :: a -> Text -> m OpenAIFile
cancelFineTuningJob :: a -> Text -> m FineTuningJob
createFineTuningJob :: a -> CreateFineTuningJobRequest -> m FineTuningJob
listFineTuningEvents :: a
-> Text
-> Maybe Text
-> Maybe Int
-> m ListFineTuningJobEventsResponse
listPaginatedFineTuningJobs :: a
-> Maybe Text -> Maybe Int -> m ListPaginatedFineTuningJobsResponse
retrieveFineTuningJob :: a -> Text -> m FineTuningJob
createImage :: a -> CreateImageRequest -> m ImagesResponse
createImageEdit :: a -> FormCreateImageEdit -> m ImagesResponse
createImageVariation :: a -> FormCreateImageVariation -> m ImagesResponse
deleteModel :: a -> Text -> m DeleteModelResponse
listModels :: a -> m ListModelsResponse
retrieveModel :: a -> Text -> m Model
createModeration :: a -> CreateModerationRequest -> m CreateModerationResponse
..} =
((a -> Text -> Text -> m RunObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> m RunObject
cancelRun a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateAssistantRequest -> m AssistantObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateAssistantRequest -> m AssistantObject
createAssistant a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject)
-> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> CreateAssistantFileRequest -> m AssistantFileObject
createAssistantFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> CreateMessageRequest -> m MessageObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> CreateMessageRequest -> m MessageObject
createMessage a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> CreateRunRequest -> m RunObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> CreateRunRequest -> m RunObject
createRun a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateThreadRequest -> m ThreadObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateThreadRequest -> m ThreadObject
createThread a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateThreadAndRunRequest -> m RunObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateThreadAndRunRequest -> m RunObject
createThreadAndRun a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m DeleteAssistantResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m DeleteAssistantResponse
deleteAssistant a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> m DeleteAssistantFileResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> m DeleteAssistantFileResponse
deleteAssistantFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m DeleteThreadResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m DeleteThreadResponse
deleteThread a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m AssistantObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m AssistantObject
getAssistant a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> m AssistantFileObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> m AssistantFileObject
getAssistantFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> m MessageObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> m MessageObject
getMessage a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> Text -> m MessageFileObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> Text -> m MessageFileObject
getMessageFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> m RunObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> m RunObject
getRun a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> Text -> m RunStepObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> Text -> m RunStepObject
getRunStep a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m ThreadObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m ThreadObject
getThread a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantFilesResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantFilesResponse
listAssistantFiles a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantsResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListAssistantsResponse
listAssistants a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessageFilesResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessageFilesResponse
listMessageFiles a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessagesResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListMessagesResponse
listMessages a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunStepsResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Text
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunStepsResponse
listRunSteps a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunsResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> m ListRunsResponse
listRuns a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> ModifyAssistantRequest -> m AssistantObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> ModifyAssistantRequest -> m AssistantObject
modifyAssistant a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> ModifyMessageRequest -> m MessageObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> ModifyMessageRequest -> m MessageObject
modifyMessage a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> ModifyRunRequest -> m RunObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> ModifyRunRequest -> m RunObject
modifyRun a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> ModifyThreadRequest -> m ThreadObject) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> ModifyThreadRequest -> m ThreadObject
modifyThread a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject)
-> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> Text -> SubmitToolOutputsRunRequest -> m RunObject
submitToolOuputsToRun a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateSpeechRequest -> m ByteString) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateSpeechRequest -> m ByteString
createSpeech a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> FormCreateTranscription -> m CreateTranscription200Response)
-> a
forall a b. Coercible a b => a -> b
coerce a -> FormCreateTranscription -> m CreateTranscription200Response
createTranscription a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> FormCreateTranslation -> m CreateTranslation200Response) -> a
forall a b. Coercible a b => a -> b
coerce a -> FormCreateTranslation -> m CreateTranslation200Response
createTranslation a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> CreateChatCompletionRequest -> m CreateChatCompletionResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a -> CreateChatCompletionRequest -> m CreateChatCompletionResponse
createChatCompletion a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateCompletionRequest -> m CreateCompletionResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateCompletionRequest -> m CreateCompletionResponse
createCompletion a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateEmbeddingRequest -> m CreateEmbeddingResponse
createEmbedding a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> FormCreateFile -> m OpenAIFile) -> a
forall a b. Coercible a b => a -> b
coerce a -> FormCreateFile -> m OpenAIFile
createFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m DeleteFileResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m DeleteFileResponse
deleteFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m Text) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m Text
downloadFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Maybe Text -> m ListFilesResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> Maybe Text -> m ListFilesResponse
listFiles a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application)))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m OpenAIFile) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m OpenAIFile
retrieveFile a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m
Application))))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m FineTuningJob) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m FineTuningJob
cancelFineTuningJob a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged m Application)))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> Tagged
m Application)))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateFineTuningJobRequest -> m FineTuningJob) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateFineTuningJobRequest -> m FineTuningJob
createFineTuningJob a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> Tagged m Application))))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a :<|> Tagged m Application))))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Text
-> Maybe Text
-> Maybe Int
-> m ListFineTuningJobEventsResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Text
-> Maybe Text
-> Maybe Int
-> m ListFineTuningJobEventsResponse
listFineTuningEvents a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application)))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application)))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a
-> Maybe Text
-> Maybe Int
-> m ListPaginatedFineTuningJobsResponse)
-> a
forall a b. Coercible a b => a -> b
coerce a
-> Maybe Text -> Maybe Int -> m ListPaginatedFineTuningJobsResponse
listPaginatedFineTuningJobs a
-> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application))))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application))))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m FineTuningJob) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m FineTuningJob
retrieveFineTuningJob a
-> (a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application)))))))
-> a
:<|> (a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application)))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateImageRequest -> m ImagesResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateImageRequest -> m ImagesResponse
createImage a
-> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application))))))
-> a
:<|> (a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application))))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> FormCreateImageEdit -> m ImagesResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> FormCreateImageEdit -> m ImagesResponse
createImageEdit a
-> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application)))))
-> a
:<|> (a
:<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application)))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> FormCreateImageVariation -> m ImagesResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> FormCreateImageVariation -> m ImagesResponse
createImageVariation a
-> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application))))
-> a :<|> (a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application))))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m DeleteModelResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m DeleteModelResponse
deleteModel a
-> (a :<|> (a :<|> (a :<|> Tagged m Application)))
-> a :<|> (a :<|> (a :<|> (a :<|> Tagged m Application)))
forall a b. a -> b -> a :<|> b
:<|>
(a -> m ListModelsResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> m ListModelsResponse
listModels a
-> (a :<|> (a :<|> Tagged m Application))
-> a :<|> (a :<|> (a :<|> Tagged m Application))
forall a b. a -> b -> a :<|> b
:<|>
(a -> Text -> m Model) -> a
forall a b. Coercible a b => a -> b
coerce a -> Text -> m Model
retrieveModel a
-> (a :<|> Tagged m Application)
-> a :<|> (a :<|> Tagged m Application)
forall a b. a -> b -> a :<|> b
:<|>
(a -> CreateModerationRequest -> m CreateModerationResponse) -> a
forall a b. Coercible a b => a -> b
coerce a -> CreateModerationRequest -> m CreateModerationResponse
createModeration a -> Tagged m Application -> a :<|> Tagged m Application
forall a b. a -> b -> a :<|> b
:<|>
FilePath -> ServerT Raw m
forall (m :: * -> *). FilePath -> ServerT Raw m
serveDirectoryFileServer FilePath
"static")
authHandler :: OpenAIAuth -> AuthHandler Request AuthServer
authHandler :: OpenAIAuth -> AuthHandler Request (AuthServerData Protected)
authHandler OpenAIAuth{ByteString -> Handler (AuthServerData Protected)
Request -> ServerError
$sel:lookupUser:OpenAIAuth :: OpenAIAuth -> ByteString -> Handler (AuthServerData Protected)
$sel:authError:OpenAIAuth :: OpenAIAuth -> Request -> ServerError
lookupUser :: ByteString -> Handler (AuthServerData Protected)
authError :: Request -> ServerError
..} = (Request -> Handler (AuthServerData Protected))
-> AuthHandler Request (AuthServerData Protected)
forall r usr. (r -> Handler usr) -> AuthHandler r usr
mkAuthHandler Request -> Handler (AuthServerData Protected)
handler
where
handler :: Request -> Handler (AuthServerData Protected)
handler Request
req = case HeaderName -> [(HeaderName, ByteString)] -> Maybe ByteString
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"Authorization" (Request -> [(HeaderName, ByteString)]
requestHeaders Request
req) of
Just ByteString
header -> case ByteString -> Maybe ByteString
extractBearerAuth ByteString
header of
Just ByteString
key -> ByteString -> Handler (AuthServerData Protected)
lookupUser ByteString
key
Maybe ByteString
Nothing -> ServerError -> Handler (AuthServerData Protected)
forall a. ServerError -> Handler a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Request -> ServerError
authError Request
req)
Maybe ByteString
Nothing -> ServerError -> Handler (AuthServerData Protected)
forall a. ServerError -> Handler a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Request -> ServerError
authError Request
req)
type Protected = AuthProtect "bearer"
type AuthServer = AuthServerData Protected
type AuthClient = AuthenticatedRequest Protected
type instance AuthClientData Protected = Text
clientAuth :: Text -> AuthClient
clientAuth :: Text -> AuthClient
clientAuth Text
key = AuthClientData Protected
-> (AuthClientData Protected -> Request -> Request) -> AuthClient
forall a.
AuthClientData a
-> (AuthClientData a -> Request -> Request)
-> AuthenticatedRequest a
mkAuthenticatedRequest (Text
"Bearer " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key) (HeaderName -> Text -> Request -> Request
forall a. ToHttpApiData a => HeaderName -> a -> Request -> Request
addHeader HeaderName
"Authorization")
serverContext :: OpenAIAuth -> Context (AuthHandler Request AuthServer ': '[])
serverContext :: OpenAIAuth
-> Context '[AuthHandler Request (AuthServerData Protected)]
serverContext OpenAIAuth
auth = OpenAIAuth -> AuthHandler Request (AuthServerData Protected)
authHandler OpenAIAuth
auth AuthHandler Request (AuthServerData Protected)
-> Context '[]
-> Context '[AuthHandler Request (AuthServerData Protected)]
forall x (xs :: [*]). x -> Context xs -> Context (x : xs)
:. Context '[]
EmptyContext