{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Resource.TextToSpeech.Text.Synthesize
(
TextSynthesizeResource
, textSynthesize
, TextSynthesize
, tsXgafv
, tsUploadProtocol
, tsAccessToken
, tsUploadType
, tsPayload
, tsCallback
) where
import Network.Google.Prelude
import Network.Google.TextToSpeech.Types
type TextSynthesizeResource =
"v1" :>
"text:synthesize" :>
QueryParam "$.xgafv" Xgafv :>
QueryParam "upload_protocol" Text :>
QueryParam "access_token" Text :>
QueryParam "uploadType" Text :>
QueryParam "callback" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] SynthesizeSpeechRequest :>
Post '[JSON] SynthesizeSpeechResponse
data TextSynthesize = TextSynthesize'
{ _tsXgafv :: !(Maybe Xgafv)
, _tsUploadProtocol :: !(Maybe Text)
, _tsAccessToken :: !(Maybe Text)
, _tsUploadType :: !(Maybe Text)
, _tsPayload :: !SynthesizeSpeechRequest
, _tsCallback :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
textSynthesize
:: SynthesizeSpeechRequest
-> TextSynthesize
textSynthesize pTsPayload_ =
TextSynthesize'
{ _tsXgafv = Nothing
, _tsUploadProtocol = Nothing
, _tsAccessToken = Nothing
, _tsUploadType = Nothing
, _tsPayload = pTsPayload_
, _tsCallback = Nothing
}
tsXgafv :: Lens' TextSynthesize (Maybe Xgafv)
tsXgafv = lens _tsXgafv (\ s a -> s{_tsXgafv = a})
tsUploadProtocol :: Lens' TextSynthesize (Maybe Text)
tsUploadProtocol
= lens _tsUploadProtocol
(\ s a -> s{_tsUploadProtocol = a})
tsAccessToken :: Lens' TextSynthesize (Maybe Text)
tsAccessToken
= lens _tsAccessToken
(\ s a -> s{_tsAccessToken = a})
tsUploadType :: Lens' TextSynthesize (Maybe Text)
tsUploadType
= lens _tsUploadType (\ s a -> s{_tsUploadType = a})
tsPayload :: Lens' TextSynthesize SynthesizeSpeechRequest
tsPayload
= lens _tsPayload (\ s a -> s{_tsPayload = a})
tsCallback :: Lens' TextSynthesize (Maybe Text)
tsCallback
= lens _tsCallback (\ s a -> s{_tsCallback = a})
instance GoogleRequest TextSynthesize where
type Rs TextSynthesize = SynthesizeSpeechResponse
type Scopes TextSynthesize =
'["https://www.googleapis.com/auth/cloud-platform"]
requestClient TextSynthesize'{..}
= go _tsXgafv _tsUploadProtocol _tsAccessToken
_tsUploadType
_tsCallback
(Just AltJSON)
_tsPayload
textToSpeechService
where go
= buildClient (Proxy :: Proxy TextSynthesizeResource)
mempty