-- | @\/v1\/audio\/speech@
module OpenAI.V1.Audio.Speech
    ( -- * Main types
      CreateSpeech(..)
    , _CreateSpeech
      -- * Other types
    , Voice(..)
    , Format(..)
      -- * Servant
    , ContentType(..)
    , API
    ) where

import OpenAI.Prelude
import OpenAI.V1.Models (Model)

-- | The voice to use when generating the audio
--
-- Previews of the voices are available in the
-- [Text to speech guide](https://platform.openai.com/docs/guides/text-to-speech#voice-options).
data Voice = Alloy | Echo | Fable | Onyx | Nova | Shimmer
    deriving stock (Voice
Voice -> Voice -> Bounded Voice
forall a. a -> a -> Bounded a
$cminBound :: Voice
minBound :: Voice
$cmaxBound :: Voice
maxBound :: Voice
Bounded, Int -> Voice
Voice -> Int
Voice -> [Voice]
Voice -> Voice
Voice -> Voice -> [Voice]
Voice -> Voice -> Voice -> [Voice]
(Voice -> Voice)
-> (Voice -> Voice)
-> (Int -> Voice)
-> (Voice -> Int)
-> (Voice -> [Voice])
-> (Voice -> Voice -> [Voice])
-> (Voice -> Voice -> [Voice])
-> (Voice -> Voice -> Voice -> [Voice])
-> Enum Voice
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Voice -> Voice
succ :: Voice -> Voice
$cpred :: Voice -> Voice
pred :: Voice -> Voice
$ctoEnum :: Int -> Voice
toEnum :: Int -> Voice
$cfromEnum :: Voice -> Int
fromEnum :: Voice -> Int
$cenumFrom :: Voice -> [Voice]
enumFrom :: Voice -> [Voice]
$cenumFromThen :: Voice -> Voice -> [Voice]
enumFromThen :: Voice -> Voice -> [Voice]
$cenumFromTo :: Voice -> Voice -> [Voice]
enumFromTo :: Voice -> Voice -> [Voice]
$cenumFromThenTo :: Voice -> Voice -> Voice -> [Voice]
enumFromThenTo :: Voice -> Voice -> Voice -> [Voice]
Enum, (forall x. Voice -> Rep Voice x)
-> (forall x. Rep Voice x -> Voice) -> Generic Voice
forall x. Rep Voice x -> Voice
forall x. Voice -> Rep Voice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Voice -> Rep Voice x
from :: forall x. Voice -> Rep Voice x
$cto :: forall x. Rep Voice x -> Voice
to :: forall x. Rep Voice x -> Voice
Generic, Int -> Voice -> ShowS
[Voice] -> ShowS
Voice -> [Char]
(Int -> Voice -> ShowS)
-> (Voice -> [Char]) -> ([Voice] -> ShowS) -> Show Voice
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Voice -> ShowS
showsPrec :: Int -> Voice -> ShowS
$cshow :: Voice -> [Char]
show :: Voice -> [Char]
$cshowList :: [Voice] -> ShowS
showList :: [Voice] -> ShowS
Show)

instance ToJSON Voice where
    toJSON :: Voice -> Value
toJSON = Options -> Voice -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

-- | The format to audio in
data Format = MP3 | Opus | AAC | FLAC | WAV | PCM
    deriving stock (Format
Format -> Format -> Bounded Format
forall a. a -> a -> Bounded a
$cminBound :: Format
minBound :: Format
$cmaxBound :: Format
maxBound :: Format
Bounded, Int -> Format
Format -> Int
Format -> [Format]
Format -> Format
Format -> Format -> [Format]
Format -> Format -> Format -> [Format]
(Format -> Format)
-> (Format -> Format)
-> (Int -> Format)
-> (Format -> Int)
-> (Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> Format -> [Format])
-> Enum Format
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Format -> Format
succ :: Format -> Format
$cpred :: Format -> Format
pred :: Format -> Format
$ctoEnum :: Int -> Format
toEnum :: Int -> Format
$cfromEnum :: Format -> Int
fromEnum :: Format -> Int
$cenumFrom :: Format -> [Format]
enumFrom :: Format -> [Format]
$cenumFromThen :: Format -> Format -> [Format]
enumFromThen :: Format -> Format -> [Format]
$cenumFromTo :: Format -> Format -> [Format]
enumFromTo :: Format -> Format -> [Format]
$cenumFromThenTo :: Format -> Format -> Format -> [Format]
enumFromThenTo :: Format -> Format -> Format -> [Format]
Enum, (forall x. Format -> Rep Format x)
-> (forall x. Rep Format x -> Format) -> Generic Format
forall x. Rep Format x -> Format
forall x. Format -> Rep Format x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Format -> Rep Format x
from :: forall x. Format -> Rep Format x
$cto :: forall x. Rep Format x -> Format
to :: forall x. Rep Format x -> Format
Generic, Int -> Format -> ShowS
[Format] -> ShowS
Format -> [Char]
(Int -> Format -> ShowS)
-> (Format -> [Char]) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Format -> ShowS
showsPrec :: Int -> Format -> ShowS
$cshow :: Format -> [Char]
show :: Format -> [Char]
$cshowList :: [Format] -> ShowS
showList :: [Format] -> ShowS
Show)

instance ToJSON Format where
    toJSON :: Format -> Value
toJSON = Options -> Format -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

-- | Request body for @\/v1\/audio\/speech@
data CreateSpeech = CreateSpeech
    { CreateSpeech -> Model
model :: Model
    , CreateSpeech -> Text
input :: Text
    , CreateSpeech -> Voice
voice :: Voice
    , CreateSpeech -> Maybe Format
response_format :: Maybe Format
    , CreateSpeech -> Maybe Double
speed :: Maybe Double
    } deriving stock ((forall x. CreateSpeech -> Rep CreateSpeech x)
-> (forall x. Rep CreateSpeech x -> CreateSpeech)
-> Generic CreateSpeech
forall x. Rep CreateSpeech x -> CreateSpeech
forall x. CreateSpeech -> Rep CreateSpeech x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateSpeech -> Rep CreateSpeech x
from :: forall x. CreateSpeech -> Rep CreateSpeech x
$cto :: forall x. Rep CreateSpeech x -> CreateSpeech
to :: forall x. Rep CreateSpeech x -> CreateSpeech
Generic, Int -> CreateSpeech -> ShowS
[CreateSpeech] -> ShowS
CreateSpeech -> [Char]
(Int -> CreateSpeech -> ShowS)
-> (CreateSpeech -> [Char])
-> ([CreateSpeech] -> ShowS)
-> Show CreateSpeech
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateSpeech -> ShowS
showsPrec :: Int -> CreateSpeech -> ShowS
$cshow :: CreateSpeech -> [Char]
show :: CreateSpeech -> [Char]
$cshowList :: [CreateSpeech] -> ShowS
showList :: [CreateSpeech] -> ShowS
Show)
      deriving anyclass ([CreateSpeech] -> Value
[CreateSpeech] -> Encoding
CreateSpeech -> Bool
CreateSpeech -> Value
CreateSpeech -> Encoding
(CreateSpeech -> Value)
-> (CreateSpeech -> Encoding)
-> ([CreateSpeech] -> Value)
-> ([CreateSpeech] -> Encoding)
-> (CreateSpeech -> Bool)
-> ToJSON CreateSpeech
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CreateSpeech -> Value
toJSON :: CreateSpeech -> Value
$ctoEncoding :: CreateSpeech -> Encoding
toEncoding :: CreateSpeech -> Encoding
$ctoJSONList :: [CreateSpeech] -> Value
toJSONList :: [CreateSpeech] -> Value
$ctoEncodingList :: [CreateSpeech] -> Encoding
toEncodingList :: [CreateSpeech] -> Encoding
$comitField :: CreateSpeech -> Bool
omitField :: CreateSpeech -> Bool
ToJSON)

-- | Default `CreateSpeech`
_CreateSpeech :: CreateSpeech
_CreateSpeech :: CreateSpeech
_CreateSpeech = CreateSpeech
    { $sel:response_format:CreateSpeech :: Maybe Format
response_format = Maybe Format
forall a. Maybe a
Nothing
    , $sel:speed:CreateSpeech :: Maybe Double
speed = Maybe Double
forall a. Maybe a
Nothing
    }

-- | Content type
data ContentType = ContentType

instance Accept ContentType where
    contentTypes :: Proxy ContentType -> NonEmpty MediaType
contentTypes Proxy ContentType
_ =
            MediaType
"audio/mpeg"
        MediaType -> [MediaType] -> NonEmpty MediaType
forall a. a -> [a] -> NonEmpty a
:|  [ Item [MediaType]
MediaType
"audio/flac"
            , Item [MediaType]
MediaType
"audio/wav"
            , Item [MediaType]
MediaType
"audio/aac"
            , Item [MediaType]
MediaType
"audio/opus"
            , Item [MediaType]
MediaType
"audio/pcm"
            ]

instance MimeUnrender ContentType ByteString where
    mimeUnrender :: Proxy ContentType -> ByteString -> Either [Char] ByteString
mimeUnrender Proxy ContentType
_ ByteString
bytes = ByteString -> Either [Char] ByteString
forall a b. b -> Either a b
Right ByteString
bytes

-- | Servant API
type API =
    "speech" :> ReqBody '[JSON] CreateSpeech :> Post '[ContentType] ByteString