module OpenAI.V1.Audio.Transcriptions
(
CreateTranscription(..)
, _CreateTranscription
, TranscriptionObject(..)
, Segment(..)
, API
) where
import OpenAI.Prelude as OpenAI.Prelude
import OpenAI.V1.Models (Model(..))
import qualified Data.Text as Text
data CreateTranscription = CreateTranscription
{ CreateTranscription -> FilePath
file :: FilePath
, CreateTranscription -> Model
model :: Model
, CreateTranscription -> Maybe Text
language :: Maybe Text
, CreateTranscription -> Maybe Text
prompt :: Maybe Text
, CreateTranscription -> Maybe Double
temperature :: Maybe Double
} deriving stock ((forall x. CreateTranscription -> Rep CreateTranscription x)
-> (forall x. Rep CreateTranscription x -> CreateTranscription)
-> Generic CreateTranscription
forall x. Rep CreateTranscription x -> CreateTranscription
forall x. CreateTranscription -> Rep CreateTranscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateTranscription -> Rep CreateTranscription x
from :: forall x. CreateTranscription -> Rep CreateTranscription x
$cto :: forall x. Rep CreateTranscription x -> CreateTranscription
to :: forall x. Rep CreateTranscription x -> CreateTranscription
Generic, Int -> CreateTranscription -> ShowS
[CreateTranscription] -> ShowS
CreateTranscription -> FilePath
(Int -> CreateTranscription -> ShowS)
-> (CreateTranscription -> FilePath)
-> ([CreateTranscription] -> ShowS)
-> Show CreateTranscription
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateTranscription -> ShowS
showsPrec :: Int -> CreateTranscription -> ShowS
$cshow :: CreateTranscription -> FilePath
show :: CreateTranscription -> FilePath
$cshowList :: [CreateTranscription] -> ShowS
showList :: [CreateTranscription] -> ShowS
Show)
instance ToMultipart Tmp CreateTranscription where
toMultipart :: CreateTranscription -> MultipartData Tmp
toMultipart CreateTranscription{ $sel:model:CreateTranscription :: CreateTranscription -> Model
model = Model Text
model, FilePath
Maybe Double
Maybe Text
$sel:file:CreateTranscription :: CreateTranscription -> FilePath
$sel:language:CreateTranscription :: CreateTranscription -> Maybe Text
$sel:prompt:CreateTranscription :: CreateTranscription -> Maybe Text
$sel:temperature:CreateTranscription :: CreateTranscription -> Maybe Double
file :: FilePath
language :: Maybe Text
prompt :: Maybe Text
temperature :: Maybe Double
..} =
MultipartData{[Input]
[FileData Tmp]
inputs :: [Input]
files :: [FileData Tmp]
inputs :: [Input]
files :: [FileData Tmp]
..}
where
inputs :: [Input]
inputs =
Text -> Text -> [Input]
input Text
"model" Text
model
[Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> (Text -> [Input]) -> Maybe Text -> [Input]
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Text -> Text -> [Input]
input Text
"language") Maybe Text
language
[Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> (Text -> [Input]) -> Maybe Text -> [Input]
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Text -> Text -> [Input]
input Text
"prompt") Maybe Text
prompt
[Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> Text -> Text -> [Input]
input Text
"response_format" Text
"verbose_json"
[Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> (Double -> [Input]) -> Maybe Double -> [Input]
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Text -> Text -> [Input]
input Text
"temperature" (Text -> [Input]) -> (Double -> Text) -> Double -> [Input]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Text
forall number. RealFloat number => number -> Text
renderRealFloat) Maybe Double
temperature
[Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> Text -> Text -> [Input]
input Text
"timestamp_granularities[]" Text
"segment"
files :: [FileData Tmp]
files = [ FileData{FilePath
Text
MultipartResult Tmp
fdInputName :: Text
fdFileName :: Text
fdFileCType :: Text
fdPayload :: FilePath
fdInputName :: Text
fdFileName :: Text
fdFileCType :: Text
fdPayload :: MultipartResult Tmp
..} ]
where
fdInputName :: Text
fdInputName = Text
"file"
fdFileName :: Text
fdFileName = FilePath -> Text
Text.pack FilePath
file
fdFileCType :: Text
fdFileCType = Text
"audio/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
getExtension FilePath
file
fdPayload :: FilePath
fdPayload = FilePath
file
_CreateTranscription :: CreateTranscription
_CreateTranscription :: CreateTranscription
_CreateTranscription = CreateTranscription
{ $sel:language:CreateTranscription :: Maybe Text
language = Maybe Text
forall a. Maybe a
Nothing
, $sel:prompt:CreateTranscription :: Maybe Text
prompt = Maybe Text
forall a. Maybe a
Nothing
, $sel:temperature:CreateTranscription :: Maybe Double
temperature = Maybe Double
forall a. Maybe a
Nothing
}
data Segment = Segment
{ Segment -> Integer
id :: Integer
, Segment -> Integer
seek :: Integer
, Segment -> Double
start :: Double
, Segment -> Double
end :: Double
, Segment -> Text
text :: Text
, Segment -> Vector Word
tokens :: Vector Prelude.Word
, Segment -> Double
temperature :: Double
, Segment -> Double
avg_logprob :: Double
, Segment -> Double
compression_ratio :: Double
, Segment -> Double
no_speech_prob :: Double
} deriving stock ((forall x. Segment -> Rep Segment x)
-> (forall x. Rep Segment x -> Segment) -> Generic Segment
forall x. Rep Segment x -> Segment
forall x. Segment -> Rep Segment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Segment -> Rep Segment x
from :: forall x. Segment -> Rep Segment x
$cto :: forall x. Rep Segment x -> Segment
to :: forall x. Rep Segment x -> Segment
Generic, Int -> Segment -> ShowS
[Segment] -> ShowS
Segment -> FilePath
(Int -> Segment -> ShowS)
-> (Segment -> FilePath) -> ([Segment] -> ShowS) -> Show Segment
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Segment -> ShowS
showsPrec :: Int -> Segment -> ShowS
$cshow :: Segment -> FilePath
show :: Segment -> FilePath
$cshowList :: [Segment] -> ShowS
showList :: [Segment] -> ShowS
Show)
deriving anyclass (Maybe Segment
Value -> Parser [Segment]
Value -> Parser Segment
(Value -> Parser Segment)
-> (Value -> Parser [Segment]) -> Maybe Segment -> FromJSON Segment
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Segment
parseJSON :: Value -> Parser Segment
$cparseJSONList :: Value -> Parser [Segment]
parseJSONList :: Value -> Parser [Segment]
$comittedField :: Maybe Segment
omittedField :: Maybe Segment
FromJSON)
data TranscriptionObject = TranscriptionObject
{ TranscriptionObject -> Maybe Text
language :: Maybe Text
, TranscriptionObject -> Maybe Double
duration :: Maybe Double
, TranscriptionObject -> Text
text :: Text
, TranscriptionObject -> Vector Segment
segments :: Vector Segment
} deriving stock ((forall x. TranscriptionObject -> Rep TranscriptionObject x)
-> (forall x. Rep TranscriptionObject x -> TranscriptionObject)
-> Generic TranscriptionObject
forall x. Rep TranscriptionObject x -> TranscriptionObject
forall x. TranscriptionObject -> Rep TranscriptionObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TranscriptionObject -> Rep TranscriptionObject x
from :: forall x. TranscriptionObject -> Rep TranscriptionObject x
$cto :: forall x. Rep TranscriptionObject x -> TranscriptionObject
to :: forall x. Rep TranscriptionObject x -> TranscriptionObject
Generic, Int -> TranscriptionObject -> ShowS
[TranscriptionObject] -> ShowS
TranscriptionObject -> FilePath
(Int -> TranscriptionObject -> ShowS)
-> (TranscriptionObject -> FilePath)
-> ([TranscriptionObject] -> ShowS)
-> Show TranscriptionObject
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TranscriptionObject -> ShowS
showsPrec :: Int -> TranscriptionObject -> ShowS
$cshow :: TranscriptionObject -> FilePath
show :: TranscriptionObject -> FilePath
$cshowList :: [TranscriptionObject] -> ShowS
showList :: [TranscriptionObject] -> ShowS
Show)
deriving anyclass (Maybe TranscriptionObject
Value -> Parser [TranscriptionObject]
Value -> Parser TranscriptionObject
(Value -> Parser TranscriptionObject)
-> (Value -> Parser [TranscriptionObject])
-> Maybe TranscriptionObject
-> FromJSON TranscriptionObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser TranscriptionObject
parseJSON :: Value -> Parser TranscriptionObject
$cparseJSONList :: Value -> Parser [TranscriptionObject]
parseJSONList :: Value -> Parser [TranscriptionObject]
$comittedField :: Maybe TranscriptionObject
omittedField :: Maybe TranscriptionObject
FromJSON)
type API =
"transcriptions"
:> MultipartForm Tmp CreateTranscription
:> Post '[JSON] TranscriptionObject