module OpenAI.V1.Files
(
FileID(..)
, UploadFile(..)
, _UploadFile
, FileObject(..)
, Order(..)
, Purpose(..)
, DeletionStatus(..)
, API
) where
import OpenAI.Prelude
import OpenAI.V1.DeletionStatus
import OpenAI.V1.ListOf
import OpenAI.V1.Order
import qualified Data.Text as Text
newtype FileID = FileID{ FileID -> Text
text :: Text }
deriving newtype (Maybe FileID
Value -> Parser [FileID]
Value -> Parser FileID
(Value -> Parser FileID)
-> (Value -> Parser [FileID]) -> Maybe FileID -> FromJSON FileID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FileID
parseJSON :: Value -> Parser FileID
$cparseJSONList :: Value -> Parser [FileID]
parseJSONList :: Value -> Parser [FileID]
$comittedField :: Maybe FileID
omittedField :: Maybe FileID
FromJSON, String -> FileID
(String -> FileID) -> IsString FileID
forall a. (String -> a) -> IsString a
$cfromString :: String -> FileID
fromString :: String -> FileID
IsString, Int -> FileID -> ShowS
[FileID] -> ShowS
FileID -> String
(Int -> FileID -> ShowS)
-> (FileID -> String) -> ([FileID] -> ShowS) -> Show FileID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileID -> ShowS
showsPrec :: Int -> FileID -> ShowS
$cshow :: FileID -> String
show :: FileID -> String
$cshowList :: [FileID] -> ShowS
showList :: [FileID] -> ShowS
Show, FileID -> Text
FileID -> ByteString
FileID -> Builder
(FileID -> Text)
-> (FileID -> Builder)
-> (FileID -> ByteString)
-> (FileID -> Text)
-> (FileID -> Builder)
-> ToHttpApiData FileID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: FileID -> Text
toUrlPiece :: FileID -> Text
$ctoEncodedUrlPiece :: FileID -> Builder
toEncodedUrlPiece :: FileID -> Builder
$ctoHeader :: FileID -> ByteString
toHeader :: FileID -> ByteString
$ctoQueryParam :: FileID -> Text
toQueryParam :: FileID -> Text
$ctoEncodedQueryParam :: FileID -> Builder
toEncodedQueryParam :: FileID -> Builder
ToHttpApiData, [FileID] -> Value
[FileID] -> Encoding
FileID -> Bool
FileID -> Value
FileID -> Encoding
(FileID -> Value)
-> (FileID -> Encoding)
-> ([FileID] -> Value)
-> ([FileID] -> Encoding)
-> (FileID -> Bool)
-> ToJSON FileID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FileID -> Value
toJSON :: FileID -> Value
$ctoEncoding :: FileID -> Encoding
toEncoding :: FileID -> Encoding
$ctoJSONList :: [FileID] -> Value
toJSONList :: [FileID] -> Value
$ctoEncodingList :: [FileID] -> Encoding
toEncodingList :: [FileID] -> Encoding
$comitField :: FileID -> Bool
omitField :: FileID -> Bool
ToJSON)
data UploadFile = UploadFile
{ UploadFile -> String
file :: FilePath
, UploadFile -> Purpose
purpose :: Purpose
} deriving stock ((forall x. UploadFile -> Rep UploadFile x)
-> (forall x. Rep UploadFile x -> UploadFile) -> Generic UploadFile
forall x. Rep UploadFile x -> UploadFile
forall x. UploadFile -> Rep UploadFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UploadFile -> Rep UploadFile x
from :: forall x. UploadFile -> Rep UploadFile x
$cto :: forall x. Rep UploadFile x -> UploadFile
to :: forall x. Rep UploadFile x -> UploadFile
Generic, Int -> UploadFile -> ShowS
[UploadFile] -> ShowS
UploadFile -> String
(Int -> UploadFile -> ShowS)
-> (UploadFile -> String)
-> ([UploadFile] -> ShowS)
-> Show UploadFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UploadFile -> ShowS
showsPrec :: Int -> UploadFile -> ShowS
$cshow :: UploadFile -> String
show :: UploadFile -> String
$cshowList :: [UploadFile] -> ShowS
showList :: [UploadFile] -> ShowS
Show)
_UploadFile :: UploadFile
_UploadFile :: UploadFile
_UploadFile = UploadFile{ }
instance ToMultipart Tmp UploadFile where
toMultipart :: UploadFile -> MultipartData Tmp
toMultipart UploadFile{String
Purpose
$sel:file:UploadFile :: UploadFile -> String
$sel:purpose:UploadFile :: UploadFile -> Purpose
file :: String
purpose :: Purpose
..} = MultipartData{[Input]
[FileData Tmp]
inputs :: [Input]
files :: [FileData Tmp]
inputs :: [Input]
files :: [FileData Tmp]
..}
where
inputs :: [Input]
inputs = Text -> Text -> [Input]
input Text
"purpose" (Purpose -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece Purpose
purpose)
files :: [FileData Tmp]
files = [ FileData{String
Text
MultipartResult Tmp
fdInputName :: Text
fdFileName :: Text
fdFileCType :: Text
fdPayload :: String
fdInputName :: Text
fdFileName :: Text
fdFileCType :: Text
fdPayload :: MultipartResult Tmp
..} ]
where
fdInputName :: Text
fdInputName = Text
"file"
fdFileName :: Text
fdFileName = String -> Text
Text.pack String
file
fdFileCType :: Text
fdFileCType = Text
"application/json"
fdPayload :: String
fdPayload = String
file
data FileObject = FileObject
{ FileObject -> FileID
id :: FileID
, FileObject -> Natural
bytes :: Natural
, FileObject -> POSIXTime
created_at :: POSIXTime
, FileObject -> Text
filename :: Text
, FileObject -> Text
object :: Text
, FileObject -> Purpose
purpose :: Purpose
} deriving stock ((forall x. FileObject -> Rep FileObject x)
-> (forall x. Rep FileObject x -> FileObject) -> Generic FileObject
forall x. Rep FileObject x -> FileObject
forall x. FileObject -> Rep FileObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FileObject -> Rep FileObject x
from :: forall x. FileObject -> Rep FileObject x
$cto :: forall x. Rep FileObject x -> FileObject
to :: forall x. Rep FileObject x -> FileObject
Generic, Int -> FileObject -> ShowS
[FileObject] -> ShowS
FileObject -> String
(Int -> FileObject -> ShowS)
-> (FileObject -> String)
-> ([FileObject] -> ShowS)
-> Show FileObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileObject -> ShowS
showsPrec :: Int -> FileObject -> ShowS
$cshow :: FileObject -> String
show :: FileObject -> String
$cshowList :: [FileObject] -> ShowS
showList :: [FileObject] -> ShowS
Show)
deriving anyclass (Maybe FileObject
Value -> Parser [FileObject]
Value -> Parser FileObject
(Value -> Parser FileObject)
-> (Value -> Parser [FileObject])
-> Maybe FileObject
-> FromJSON FileObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FileObject
parseJSON :: Value -> Parser FileObject
$cparseJSONList :: Value -> Parser [FileObject]
parseJSONList :: Value -> Parser [FileObject]
$comittedField :: Maybe FileObject
omittedField :: Maybe FileObject
FromJSON)
data Purpose
= Assistants
| Assistants_Output
| Batch
| Batch_Output
| Fine_Tune
| Fine_Tune_Results
| Vision
deriving stock ((forall x. Purpose -> Rep Purpose x)
-> (forall x. Rep Purpose x -> Purpose) -> Generic Purpose
forall x. Rep Purpose x -> Purpose
forall x. Purpose -> Rep Purpose x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Purpose -> Rep Purpose x
from :: forall x. Purpose -> Rep Purpose x
$cto :: forall x. Rep Purpose x -> Purpose
to :: forall x. Rep Purpose x -> Purpose
Generic, Int -> Purpose -> ShowS
[Purpose] -> ShowS
Purpose -> String
(Int -> Purpose -> ShowS)
-> (Purpose -> String) -> ([Purpose] -> ShowS) -> Show Purpose
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Purpose -> ShowS
showsPrec :: Int -> Purpose -> ShowS
$cshow :: Purpose -> String
show :: Purpose -> String
$cshowList :: [Purpose] -> ShowS
showList :: [Purpose] -> ShowS
Show)
purposeOptions :: Options
purposeOptions :: Options
purposeOptions = Options
aesonOptions
{ constructorTagModifier = fix . labelModifier }
where
fix :: a -> a
fix a
"fine_tune" = a
"fine-tune"
fix a
"fine_tune_results" = a
"fine-tune-results"
fix a
string = a
string
instance FromJSON Purpose where
parseJSON :: Value -> Parser Purpose
parseJSON = Options -> Value -> Parser Purpose
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
purposeOptions
instance ToJSON Purpose where
toJSON :: Purpose -> Value
toJSON = Options -> Purpose -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
purposeOptions
instance ToHttpApiData Purpose where
toUrlPiece :: Purpose -> Text
toUrlPiece Purpose
Assistants = Text
"assistants"
toUrlPiece Purpose
Assistants_Output = Text
"assistants"
toUrlPiece Purpose
Batch = Text
"batch"
toUrlPiece Purpose
Batch_Output = Text
"batch_output"
toUrlPiece Purpose
Fine_Tune = Text
"fine-tune"
toUrlPiece Purpose
Fine_Tune_Results = Text
"fine-tune-results"
toUrlPiece Purpose
Vision = Text
"vision"
type API =
"files"
:> ( MultipartForm Tmp UploadFile
:> Post '[JSON] FileObject
:<|> QueryParam "purpose" Purpose
:> QueryParam "limit" Natural
:> QueryParam "order" Order
:> QueryParam "after" Text
:> Get '[JSON] (ListOf FileObject)
:<|> Capture "file_id" FileID
:> Get '[JSON] FileObject
:<|> Capture "file_id" FileID
:> Delete '[JSON] DeletionStatus
:<|> Capture "file_id" FileID
:> "content"
:> Get '[OctetStream] ByteString
)