{-# LANGUAGE InstanceSigs #-}
module OpenAI.V1.Uploads
(
UploadID(..)
, CreateUpload(..)
, _CreateUpload
, AddUploadPart(..)
, _AddUploadPart
, CompleteUpload(..)
, _CompleteUpload
, UploadObject(..)
, PartObject(..)
, Status(..)
, API
) where
import OpenAI.Prelude
import OpenAI.V1.Files (FileObject, Purpose)
import qualified Data.Text as Text
newtype UploadID = UploadID{ UploadID -> Text
text :: Text }
deriving newtype (Maybe UploadID
Value -> Parser [UploadID]
Value -> Parser UploadID
(Value -> Parser UploadID)
-> (Value -> Parser [UploadID])
-> Maybe UploadID
-> FromJSON UploadID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UploadID
parseJSON :: Value -> Parser UploadID
$cparseJSONList :: Value -> Parser [UploadID]
parseJSONList :: Value -> Parser [UploadID]
$comittedField :: Maybe UploadID
omittedField :: Maybe UploadID
FromJSON, String -> UploadID
(String -> UploadID) -> IsString UploadID
forall a. (String -> a) -> IsString a
$cfromString :: String -> UploadID
fromString :: String -> UploadID
IsString, Int -> UploadID -> ShowS
[UploadID] -> ShowS
UploadID -> String
(Int -> UploadID -> ShowS)
-> (UploadID -> String) -> ([UploadID] -> ShowS) -> Show UploadID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UploadID -> ShowS
showsPrec :: Int -> UploadID -> ShowS
$cshow :: UploadID -> String
show :: UploadID -> String
$cshowList :: [UploadID] -> ShowS
showList :: [UploadID] -> ShowS
Show, UploadID -> Text
UploadID -> ByteString
UploadID -> Builder
(UploadID -> Text)
-> (UploadID -> Builder)
-> (UploadID -> ByteString)
-> (UploadID -> Text)
-> (UploadID -> Builder)
-> ToHttpApiData UploadID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: UploadID -> Text
toUrlPiece :: UploadID -> Text
$ctoEncodedUrlPiece :: UploadID -> Builder
toEncodedUrlPiece :: UploadID -> Builder
$ctoHeader :: UploadID -> ByteString
toHeader :: UploadID -> ByteString
$ctoQueryParam :: UploadID -> Text
toQueryParam :: UploadID -> Text
$ctoEncodedQueryParam :: UploadID -> Builder
toEncodedQueryParam :: UploadID -> Builder
ToHttpApiData, [UploadID] -> Value
[UploadID] -> Encoding
UploadID -> Bool
UploadID -> Value
UploadID -> Encoding
(UploadID -> Value)
-> (UploadID -> Encoding)
-> ([UploadID] -> Value)
-> ([UploadID] -> Encoding)
-> (UploadID -> Bool)
-> ToJSON UploadID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UploadID -> Value
toJSON :: UploadID -> Value
$ctoEncoding :: UploadID -> Encoding
toEncoding :: UploadID -> Encoding
$ctoJSONList :: [UploadID] -> Value
toJSONList :: [UploadID] -> Value
$ctoEncodingList :: [UploadID] -> Encoding
toEncodingList :: [UploadID] -> Encoding
$comitField :: UploadID -> Bool
omitField :: UploadID -> Bool
ToJSON)
data CreateUpload = CreateUpload
{ CreateUpload -> Text
filename :: Text
, CreateUpload -> Purpose
purpose :: Purpose
, CreateUpload -> Natural
bytes :: Natural
, CreateUpload -> Text
mime_type :: Text
} deriving stock ((forall x. CreateUpload -> Rep CreateUpload x)
-> (forall x. Rep CreateUpload x -> CreateUpload)
-> Generic CreateUpload
forall x. Rep CreateUpload x -> CreateUpload
forall x. CreateUpload -> Rep CreateUpload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateUpload -> Rep CreateUpload x
from :: forall x. CreateUpload -> Rep CreateUpload x
$cto :: forall x. Rep CreateUpload x -> CreateUpload
to :: forall x. Rep CreateUpload x -> CreateUpload
Generic, Int -> CreateUpload -> ShowS
[CreateUpload] -> ShowS
CreateUpload -> String
(Int -> CreateUpload -> ShowS)
-> (CreateUpload -> String)
-> ([CreateUpload] -> ShowS)
-> Show CreateUpload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateUpload -> ShowS
showsPrec :: Int -> CreateUpload -> ShowS
$cshow :: CreateUpload -> String
show :: CreateUpload -> String
$cshowList :: [CreateUpload] -> ShowS
showList :: [CreateUpload] -> ShowS
Show)
deriving anyclass ([CreateUpload] -> Value
[CreateUpload] -> Encoding
CreateUpload -> Bool
CreateUpload -> Value
CreateUpload -> Encoding
(CreateUpload -> Value)
-> (CreateUpload -> Encoding)
-> ([CreateUpload] -> Value)
-> ([CreateUpload] -> Encoding)
-> (CreateUpload -> Bool)
-> ToJSON CreateUpload
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CreateUpload -> Value
toJSON :: CreateUpload -> Value
$ctoEncoding :: CreateUpload -> Encoding
toEncoding :: CreateUpload -> Encoding
$ctoJSONList :: [CreateUpload] -> Value
toJSONList :: [CreateUpload] -> Value
$ctoEncodingList :: [CreateUpload] -> Encoding
toEncodingList :: [CreateUpload] -> Encoding
$comitField :: CreateUpload -> Bool
omitField :: CreateUpload -> Bool
ToJSON)
_CreateUpload :: CreateUpload
_CreateUpload :: CreateUpload
_CreateUpload = CreateUpload{ }
data AddUploadPart = AddUploadPart{ AddUploadPart -> String
data_ :: FilePath }
_AddUploadPart :: AddUploadPart
_AddUploadPart :: AddUploadPart
_AddUploadPart = AddUploadPart{ }
instance ToMultipart Tmp AddUploadPart where
toMultipart :: AddUploadPart -> MultipartData Tmp
toMultipart AddUploadPart{String
$sel:data_:AddUploadPart :: AddUploadPart -> String
data_ :: String
..} = MultipartData{[Input]
[FileData Tmp]
inputs :: [Input]
files :: [FileData Tmp]
inputs :: [Input]
files :: [FileData Tmp]
..}
where
inputs :: [Input]
inputs = [Input]
forall a. Monoid a => a
mempty
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
"data"
fdFileName :: Text
fdFileName = String -> Text
Text.pack String
data_
fdFileCType :: Text
fdFileCType = Text
"application/octet-stream"
fdPayload :: String
fdPayload = String
data_
data CompleteUpload = CompleteUpload
{ CompleteUpload -> Vector Text
part_ids :: Vector Text
, CompleteUpload -> Maybe Text
md5 :: Maybe Text
} deriving stock ((forall x. CompleteUpload -> Rep CompleteUpload x)
-> (forall x. Rep CompleteUpload x -> CompleteUpload)
-> Generic CompleteUpload
forall x. Rep CompleteUpload x -> CompleteUpload
forall x. CompleteUpload -> Rep CompleteUpload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CompleteUpload -> Rep CompleteUpload x
from :: forall x. CompleteUpload -> Rep CompleteUpload x
$cto :: forall x. Rep CompleteUpload x -> CompleteUpload
to :: forall x. Rep CompleteUpload x -> CompleteUpload
Generic, Int -> CompleteUpload -> ShowS
[CompleteUpload] -> ShowS
CompleteUpload -> String
(Int -> CompleteUpload -> ShowS)
-> (CompleteUpload -> String)
-> ([CompleteUpload] -> ShowS)
-> Show CompleteUpload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompleteUpload -> ShowS
showsPrec :: Int -> CompleteUpload -> ShowS
$cshow :: CompleteUpload -> String
show :: CompleteUpload -> String
$cshowList :: [CompleteUpload] -> ShowS
showList :: [CompleteUpload] -> ShowS
Show)
_CompleteUpload :: CompleteUpload
_CompleteUpload :: CompleteUpload
_CompleteUpload = CompleteUpload
{ $sel:md5:CompleteUpload :: Maybe Text
md5 = Maybe Text
forall a. Maybe a
Nothing
}
instance ToJSON CompleteUpload where
toJSON :: CompleteUpload -> Value
toJSON CompleteUpload
completeUpload = Options -> CompleteUpload -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions (CompleteUpload -> CompleteUpload
fix CompleteUpload
completeUpload)
where
fix :: CompleteUpload -> CompleteUpload
fix CompleteUpload{ $sel:md5:CompleteUpload :: CompleteUpload -> Maybe Text
md5 = Maybe Text
Nothing, Vector Text
$sel:part_ids:CompleteUpload :: CompleteUpload -> Vector Text
part_ids :: Vector Text
.. } =
CompleteUpload{ $sel:md5:CompleteUpload :: Maybe Text
md5 = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"", Vector Text
$sel:part_ids:CompleteUpload :: Vector Text
part_ids :: Vector Text
.. }
fix CompleteUpload
x = CompleteUpload
x
data Status
= Pending
| Completed
| Cancelled
| Expired
deriving stock ((forall x. Status -> Rep Status x)
-> (forall x. Rep Status x -> Status) -> Generic Status
forall x. Rep Status x -> Status
forall x. Status -> Rep Status x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Status -> Rep Status x
from :: forall x. Status -> Rep Status x
$cto :: forall x. Rep Status x -> Status
to :: forall x. Rep Status x -> Status
Generic, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
(Int -> Status -> ShowS)
-> (Status -> String) -> ([Status] -> ShowS) -> Show Status
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Status -> ShowS
showsPrec :: Int -> Status -> ShowS
$cshow :: Status -> String
show :: Status -> String
$cshowList :: [Status] -> ShowS
showList :: [Status] -> ShowS
Show)
instance FromJSON Status where
parseJSON :: Value -> Parser Status
parseJSON = Options -> Value -> Parser Status
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
data UploadObject file = UploadObject
{ forall file. UploadObject file -> UploadID
id :: UploadID
, forall file. UploadObject file -> POSIXTime
created_at :: POSIXTime
, forall file. UploadObject file -> Text
filename :: Text
, forall file. UploadObject file -> Natural
bytes :: Natural
, forall file. UploadObject file -> Purpose
purpose :: Purpose
, forall file. UploadObject file -> Status
status :: Status
, forall file. UploadObject file -> POSIXTime
expires_at :: POSIXTime
, forall file. UploadObject file -> Text
object :: Text
, forall file. UploadObject file -> file
file :: file
} deriving stock ((forall x. UploadObject file -> Rep (UploadObject file) x)
-> (forall x. Rep (UploadObject file) x -> UploadObject file)
-> Generic (UploadObject file)
forall x. Rep (UploadObject file) x -> UploadObject file
forall x. UploadObject file -> Rep (UploadObject file) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall file x. Rep (UploadObject file) x -> UploadObject file
forall file x. UploadObject file -> Rep (UploadObject file) x
$cfrom :: forall file x. UploadObject file -> Rep (UploadObject file) x
from :: forall x. UploadObject file -> Rep (UploadObject file) x
$cto :: forall file x. Rep (UploadObject file) x -> UploadObject file
to :: forall x. Rep (UploadObject file) x -> UploadObject file
Generic, Int -> UploadObject file -> ShowS
[UploadObject file] -> ShowS
UploadObject file -> String
(Int -> UploadObject file -> ShowS)
-> (UploadObject file -> String)
-> ([UploadObject file] -> ShowS)
-> Show (UploadObject file)
forall file. Show file => Int -> UploadObject file -> ShowS
forall file. Show file => [UploadObject file] -> ShowS
forall file. Show file => UploadObject file -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall file. Show file => Int -> UploadObject file -> ShowS
showsPrec :: Int -> UploadObject file -> ShowS
$cshow :: forall file. Show file => UploadObject file -> String
show :: UploadObject file -> String
$cshowList :: forall file. Show file => [UploadObject file] -> ShowS
showList :: [UploadObject file] -> ShowS
Show)
instance FromJSON (UploadObject (Maybe Void))
instance FromJSON (UploadObject FileObject)
data PartObject = PartObject
{ PartObject -> Text
id :: Text
, PartObject -> POSIXTime
created_at :: POSIXTime
, PartObject -> UploadID
upload_id :: UploadID
, PartObject -> Text
object :: Text
} deriving stock ((forall x. PartObject -> Rep PartObject x)
-> (forall x. Rep PartObject x -> PartObject) -> Generic PartObject
forall x. Rep PartObject x -> PartObject
forall x. PartObject -> Rep PartObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PartObject -> Rep PartObject x
from :: forall x. PartObject -> Rep PartObject x
$cto :: forall x. Rep PartObject x -> PartObject
to :: forall x. Rep PartObject x -> PartObject
Generic, Int -> PartObject -> ShowS
[PartObject] -> ShowS
PartObject -> String
(Int -> PartObject -> ShowS)
-> (PartObject -> String)
-> ([PartObject] -> ShowS)
-> Show PartObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PartObject -> ShowS
showsPrec :: Int -> PartObject -> ShowS
$cshow :: PartObject -> String
show :: PartObject -> String
$cshowList :: [PartObject] -> ShowS
showList :: [PartObject] -> ShowS
Show)
deriving anyclass (Maybe PartObject
Value -> Parser [PartObject]
Value -> Parser PartObject
(Value -> Parser PartObject)
-> (Value -> Parser [PartObject])
-> Maybe PartObject
-> FromJSON PartObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PartObject
parseJSON :: Value -> Parser PartObject
$cparseJSONList :: Value -> Parser [PartObject]
parseJSONList :: Value -> Parser [PartObject]
$comittedField :: Maybe PartObject
omittedField :: Maybe PartObject
FromJSON)
type API
= "uploads"
:> ( ReqBody '[JSON] CreateUpload
:> Post '[JSON] (UploadObject (Maybe Void))
:<|> Capture "upload_id" UploadID
:> "parts"
:> MultipartForm Tmp AddUploadPart
:> Post '[JSON] PartObject
:<|> Capture "upload_id" UploadID
:> "complete"
:> ReqBody '[JSON] CompleteUpload
:> Post '[JSON] (UploadObject FileObject)
:<|> Capture "upload_id" UploadID
:> "cancel"
:> Post '[JSON] (UploadObject (Maybe Void))
)