gogol-texttospeech-0.4.0: Google Cloud Text-to-Speech SDK.

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Google.TextToSpeech.Types

Contents

Description

 
Synopsis

Service Configuration

textToSpeechService :: ServiceConfig Source #

Default request referring to version v1 of the Cloud Text-to-Speech API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

cloudPlatformScope :: Proxy '["https://www.googleapis.com/auth/cloud-platform"] Source #

View and manage your data across Google Cloud Platform services

AudioConfig

data AudioConfig Source #

Description of audio data to be synthesized.

See: audioConfig smart constructor.

Instances
Eq AudioConfig Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Data AudioConfig Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AudioConfig -> c AudioConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AudioConfig #

toConstr :: AudioConfig -> Constr #

dataTypeOf :: AudioConfig -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AudioConfig) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AudioConfig) #

gmapT :: (forall b. Data b => b -> b) -> AudioConfig -> AudioConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AudioConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AudioConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> AudioConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AudioConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AudioConfig -> m AudioConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioConfig -> m AudioConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioConfig -> m AudioConfig #

Show AudioConfig Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Generic AudioConfig Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Associated Types

type Rep AudioConfig :: Type -> Type #

ToJSON AudioConfig Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

FromJSON AudioConfig Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep AudioConfig Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep AudioConfig = D1 (MetaData "AudioConfig" "Network.Google.TextToSpeech.Types.Product" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) (C1 (MetaCons "AudioConfig'" PrefixI True) ((S1 (MetaSel (Just "_acVolumeGainDB") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_acSampleRateHertz") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) :*: (S1 (MetaSel (Just "_acAudioEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AudioConfigAudioEncoding)) :*: (S1 (MetaSel (Just "_acSpeakingRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_acPitch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))))

audioConfig :: AudioConfig Source #

Creates a value of AudioConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

acVolumeGainDB :: Lens' AudioConfig (Maybe Double) Source #

Optional volume gain (in dB) of the normal native volume supported by the specific voice, in the range [-96.0, 16.0]. If unset, or set to a value of 0.0 (dB), will play at normal native signal amplitude. A value of -6.0 (dB) will play at approximately half the amplitude of the normal native signal amplitude. A value of +6.0 (dB) will play at approximately twice the amplitude of the normal native signal amplitude. Strongly recommend not to exceed +10 (dB) as there's usually no effective increase in loudness for any value greater than that.

acSampleRateHertz :: Lens' AudioConfig (Maybe Int32) Source #

The synthesis sample rate (in hertz) for this audio. Optional. If this is different from the voice's natural sample rate, then the synthesizer will honor this request by converting to the desired sample rate (which might result in worse audio quality), unless the specified sample rate is not supported for the encoding chosen, in which case it will fail the request and return google.rpc.Code.INVALID_ARGUMENT.

acAudioEncoding :: Lens' AudioConfig (Maybe AudioConfigAudioEncoding) Source #

Required. The format of the requested audio byte stream.

acSpeakingRate :: Lens' AudioConfig (Maybe Double) Source #

Optional speaking rate/speed, in the range [0.25, 4.0]. 1.0 is the normal native speed supported by the specific voice. 2.0 is twice as fast, and 0.5 is half as fast. If unset(0.0), defaults to the native 1.0 speed. Any other values < 0.25 or > 4.0 will return an error.

acPitch :: Lens' AudioConfig (Maybe Double) Source #

Optional speaking pitch, in the range [-20.0, 20.0]. 20 means increase 20 semitones from the original pitch. -20 means decrease 20 semitones from the original pitch.

VoiceSelectionParams

data VoiceSelectionParams Source #

Description of which voice to use for a synthesis request.

See: voiceSelectionParams smart constructor.

Instances
Eq VoiceSelectionParams Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Data VoiceSelectionParams Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VoiceSelectionParams -> c VoiceSelectionParams #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VoiceSelectionParams #

toConstr :: VoiceSelectionParams -> Constr #

dataTypeOf :: VoiceSelectionParams -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VoiceSelectionParams) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VoiceSelectionParams) #

gmapT :: (forall b. Data b => b -> b) -> VoiceSelectionParams -> VoiceSelectionParams #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VoiceSelectionParams -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VoiceSelectionParams -> r #

gmapQ :: (forall d. Data d => d -> u) -> VoiceSelectionParams -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VoiceSelectionParams -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VoiceSelectionParams -> m VoiceSelectionParams #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VoiceSelectionParams -> m VoiceSelectionParams #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VoiceSelectionParams -> m VoiceSelectionParams #

Show VoiceSelectionParams Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Generic VoiceSelectionParams Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Associated Types

type Rep VoiceSelectionParams :: Type -> Type #

ToJSON VoiceSelectionParams Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

FromJSON VoiceSelectionParams Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep VoiceSelectionParams Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep VoiceSelectionParams = D1 (MetaData "VoiceSelectionParams" "Network.Google.TextToSpeech.Types.Product" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) (C1 (MetaCons "VoiceSelectionParams'" PrefixI True) (S1 (MetaSel (Just "_vspLanguageCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_vspSsmlGender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VoiceSelectionParamsSsmlGender)) :*: S1 (MetaSel (Just "_vspName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

voiceSelectionParams :: VoiceSelectionParams Source #

Creates a value of VoiceSelectionParams with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

vspLanguageCode :: Lens' VoiceSelectionParams (Maybe Text) Source #

The language (and optionally also the region) of the voice expressed as a BCP-47 language tag, e.g. "en-US". Required. This should not include a script tag (e.g. use "cmn-cn" rather than "cmn-Hant-cn"), because the script will be inferred from the input provided in the SynthesisInput. The TTS service will use this parameter to help choose an appropriate voice. Note that the TTS service may choose a voice with a slightly different language code than the one selected; it may substitute a different region (e.g. using en-US rather than en-CA if there isn't a Canadian voice available), or even a different language, e.g. using "nb" (Norwegian Bokmal) instead of "no" (Norwegian)".

vspSsmlGender :: Lens' VoiceSelectionParams (Maybe VoiceSelectionParamsSsmlGender) Source #

The preferred gender of the voice. Optional; if not set, the service will choose a voice based on the other parameters such as language_code and name. Note that this is only a preference, not requirement; if a voice of the appropriate gender is not available, the synthesizer should substitute a voice with a different gender rather than failing the request.

vspName :: Lens' VoiceSelectionParams (Maybe Text) Source #

The name of the voice. Optional; if not set, the service will choose a voice based on the other parameters such as language_code and gender.

SynthesizeSpeechRequest

data SynthesizeSpeechRequest Source #

The top-level message sent by the client for the `SynthesizeSpeech` method.

See: synthesizeSpeechRequest smart constructor.

Instances
Eq SynthesizeSpeechRequest Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Data SynthesizeSpeechRequest Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SynthesizeSpeechRequest -> c SynthesizeSpeechRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SynthesizeSpeechRequest #

toConstr :: SynthesizeSpeechRequest -> Constr #

dataTypeOf :: SynthesizeSpeechRequest -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SynthesizeSpeechRequest) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SynthesizeSpeechRequest) #

gmapT :: (forall b. Data b => b -> b) -> SynthesizeSpeechRequest -> SynthesizeSpeechRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SynthesizeSpeechRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SynthesizeSpeechRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> SynthesizeSpeechRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SynthesizeSpeechRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SynthesizeSpeechRequest -> m SynthesizeSpeechRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthesizeSpeechRequest -> m SynthesizeSpeechRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthesizeSpeechRequest -> m SynthesizeSpeechRequest #

Show SynthesizeSpeechRequest Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Generic SynthesizeSpeechRequest Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Associated Types

type Rep SynthesizeSpeechRequest :: Type -> Type #

ToJSON SynthesizeSpeechRequest Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

FromJSON SynthesizeSpeechRequest Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep SynthesizeSpeechRequest Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep SynthesizeSpeechRequest = D1 (MetaData "SynthesizeSpeechRequest" "Network.Google.TextToSpeech.Types.Product" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) (C1 (MetaCons "SynthesizeSpeechRequest'" PrefixI True) (S1 (MetaSel (Just "_ssrAudioConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AudioConfig)) :*: (S1 (MetaSel (Just "_ssrInput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SynthesisInput)) :*: S1 (MetaSel (Just "_ssrVoice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VoiceSelectionParams)))))

synthesizeSpeechRequest :: SynthesizeSpeechRequest Source #

Creates a value of SynthesizeSpeechRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ssrAudioConfig :: Lens' SynthesizeSpeechRequest (Maybe AudioConfig) Source #

Required. The configuration of the synthesized audio.

ssrInput :: Lens' SynthesizeSpeechRequest (Maybe SynthesisInput) Source #

Required. The Synthesizer requires either plain text or SSML as input.

ssrVoice :: Lens' SynthesizeSpeechRequest (Maybe VoiceSelectionParams) Source #

Required. The desired voice of the synthesized audio.

ListVoicesResponse

data ListVoicesResponse Source #

The message returned to the client by the `ListVoices` method.

See: listVoicesResponse smart constructor.

Instances
Eq ListVoicesResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Data ListVoicesResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListVoicesResponse -> c ListVoicesResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListVoicesResponse #

toConstr :: ListVoicesResponse -> Constr #

dataTypeOf :: ListVoicesResponse -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListVoicesResponse) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListVoicesResponse) #

gmapT :: (forall b. Data b => b -> b) -> ListVoicesResponse -> ListVoicesResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListVoicesResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListVoicesResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ListVoicesResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListVoicesResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListVoicesResponse -> m ListVoicesResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListVoicesResponse -> m ListVoicesResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListVoicesResponse -> m ListVoicesResponse #

Show ListVoicesResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Generic ListVoicesResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Associated Types

type Rep ListVoicesResponse :: Type -> Type #

ToJSON ListVoicesResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

FromJSON ListVoicesResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep ListVoicesResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep ListVoicesResponse = D1 (MetaData "ListVoicesResponse" "Network.Google.TextToSpeech.Types.Product" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" True) (C1 (MetaCons "ListVoicesResponse'" PrefixI True) (S1 (MetaSel (Just "_lvrVoices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Voice]))))

listVoicesResponse :: ListVoicesResponse Source #

Creates a value of ListVoicesResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

VoiceSelectionParamsSsmlGender

data VoiceSelectionParamsSsmlGender Source #

The preferred gender of the voice. Optional; if not set, the service will choose a voice based on the other parameters such as language_code and name. Note that this is only a preference, not requirement; if a voice of the appropriate gender is not available, the synthesizer should substitute a voice with a different gender rather than failing the request.

Constructors

SsmlVoiceGenderUnspecified

SSML_VOICE_GENDER_UNSPECIFIED An unspecified gender. In VoiceSelectionParams, this means that the client doesn't care which gender the selected voice will have. In the Voice field of ListVoicesResponse, this may mean that the voice doesn't fit any of the other categories in this enum, or that the gender of the voice isn't known.

Male

MALE A male voice.

Female

FEMALE A female voice.

Neutral

NEUTRAL A gender-neutral voice.

Instances
Enum VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Eq VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Data VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VoiceSelectionParamsSsmlGender -> c VoiceSelectionParamsSsmlGender #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VoiceSelectionParamsSsmlGender #

toConstr :: VoiceSelectionParamsSsmlGender -> Constr #

dataTypeOf :: VoiceSelectionParamsSsmlGender -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VoiceSelectionParamsSsmlGender) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VoiceSelectionParamsSsmlGender) #

gmapT :: (forall b. Data b => b -> b) -> VoiceSelectionParamsSsmlGender -> VoiceSelectionParamsSsmlGender #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VoiceSelectionParamsSsmlGender -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VoiceSelectionParamsSsmlGender -> r #

gmapQ :: (forall d. Data d => d -> u) -> VoiceSelectionParamsSsmlGender -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VoiceSelectionParamsSsmlGender -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VoiceSelectionParamsSsmlGender -> m VoiceSelectionParamsSsmlGender #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VoiceSelectionParamsSsmlGender -> m VoiceSelectionParamsSsmlGender #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VoiceSelectionParamsSsmlGender -> m VoiceSelectionParamsSsmlGender #

Ord VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Read VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Show VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Generic VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Associated Types

type Rep VoiceSelectionParamsSsmlGender :: Type -> Type #

Hashable VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

ToJSON VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromJSON VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromHttpApiData VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

ToHttpApiData VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep VoiceSelectionParamsSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep VoiceSelectionParamsSsmlGender = D1 (MetaData "VoiceSelectionParamsSsmlGender" "Network.Google.TextToSpeech.Types.Sum" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) ((C1 (MetaCons "SsmlVoiceGenderUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Male" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Female" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Neutral" PrefixI False) (U1 :: Type -> Type)))

SynthesisInput

data SynthesisInput Source #

Contains text input to be synthesized. Either `text` or `ssml` must be supplied. Supplying both or neither returns google.rpc.Code.INVALID_ARGUMENT. The input size is limited to 5000 characters.

See: synthesisInput smart constructor.

Instances
Eq SynthesisInput Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Data SynthesisInput Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SynthesisInput -> c SynthesisInput #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SynthesisInput #

toConstr :: SynthesisInput -> Constr #

dataTypeOf :: SynthesisInput -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SynthesisInput) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SynthesisInput) #

gmapT :: (forall b. Data b => b -> b) -> SynthesisInput -> SynthesisInput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SynthesisInput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SynthesisInput -> r #

gmapQ :: (forall d. Data d => d -> u) -> SynthesisInput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SynthesisInput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SynthesisInput -> m SynthesisInput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthesisInput -> m SynthesisInput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthesisInput -> m SynthesisInput #

Show SynthesisInput Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Generic SynthesisInput Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Associated Types

type Rep SynthesisInput :: Type -> Type #

ToJSON SynthesisInput Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

FromJSON SynthesisInput Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep SynthesisInput Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep SynthesisInput = D1 (MetaData "SynthesisInput" "Network.Google.TextToSpeech.Types.Product" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) (C1 (MetaCons "SynthesisInput'" PrefixI True) (S1 (MetaSel (Just "_siText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_siSsml") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

synthesisInput :: SynthesisInput Source #

Creates a value of SynthesisInput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

siText :: Lens' SynthesisInput (Maybe Text) Source #

The raw text to be synthesized.

siSsml :: Lens' SynthesisInput (Maybe Text) Source #

The SSML document to be synthesized. The SSML document must be valid and well-formed. Otherwise the RPC will fail and return google.rpc.Code.INVALID_ARGUMENT. For more information, see SSML.

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances
Enum Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

(==) :: Xgafv -> Xgafv -> Bool #

(/=) :: Xgafv -> Xgafv -> Bool #

Data Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Xgafv -> c Xgafv #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Xgafv #

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Xgafv) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xgafv) #

gmapT :: (forall b. Data b => b -> b) -> Xgafv -> Xgafv #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQ :: (forall d. Data d => d -> u) -> Xgafv -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Xgafv -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

Ord Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

compare :: Xgafv -> Xgafv -> Ordering #

(<) :: Xgafv -> Xgafv -> Bool #

(<=) :: Xgafv -> Xgafv -> Bool #

(>) :: Xgafv -> Xgafv -> Bool #

(>=) :: Xgafv -> Xgafv -> Bool #

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Associated Types

type Rep Xgafv :: Type -> Type #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.TextToSpeech.Types.Sum" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) (C1 (MetaCons "X1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "X2" PrefixI False) (U1 :: Type -> Type))

VoiceSsmlGender

data VoiceSsmlGender Source #

The gender of this voice.

Constructors

VSGSsmlVoiceGenderUnspecified

SSML_VOICE_GENDER_UNSPECIFIED An unspecified gender. In VoiceSelectionParams, this means that the client doesn't care which gender the selected voice will have. In the Voice field of ListVoicesResponse, this may mean that the voice doesn't fit any of the other categories in this enum, or that the gender of the voice isn't known.

VSGMale

MALE A male voice.

VSGFemale

FEMALE A female voice.

VSGNeutral

NEUTRAL A gender-neutral voice.

Instances
Enum VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Eq VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Data VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VoiceSsmlGender -> c VoiceSsmlGender #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VoiceSsmlGender #

toConstr :: VoiceSsmlGender -> Constr #

dataTypeOf :: VoiceSsmlGender -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VoiceSsmlGender) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VoiceSsmlGender) #

gmapT :: (forall b. Data b => b -> b) -> VoiceSsmlGender -> VoiceSsmlGender #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VoiceSsmlGender -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VoiceSsmlGender -> r #

gmapQ :: (forall d. Data d => d -> u) -> VoiceSsmlGender -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VoiceSsmlGender -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VoiceSsmlGender -> m VoiceSsmlGender #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VoiceSsmlGender -> m VoiceSsmlGender #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VoiceSsmlGender -> m VoiceSsmlGender #

Ord VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Read VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Show VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Generic VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Associated Types

type Rep VoiceSsmlGender :: Type -> Type #

Hashable VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

ToJSON VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromJSON VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromHttpApiData VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

ToHttpApiData VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep VoiceSsmlGender Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep VoiceSsmlGender = D1 (MetaData "VoiceSsmlGender" "Network.Google.TextToSpeech.Types.Sum" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) ((C1 (MetaCons "VSGSsmlVoiceGenderUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VSGMale" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VSGFemale" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VSGNeutral" PrefixI False) (U1 :: Type -> Type)))

SynthesizeSpeechResponse

data SynthesizeSpeechResponse Source #

The message returned to the client by the `SynthesizeSpeech` method.

See: synthesizeSpeechResponse smart constructor.

Instances
Eq SynthesizeSpeechResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Data SynthesizeSpeechResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SynthesizeSpeechResponse -> c SynthesizeSpeechResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SynthesizeSpeechResponse #

toConstr :: SynthesizeSpeechResponse -> Constr #

dataTypeOf :: SynthesizeSpeechResponse -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SynthesizeSpeechResponse) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SynthesizeSpeechResponse) #

gmapT :: (forall b. Data b => b -> b) -> SynthesizeSpeechResponse -> SynthesizeSpeechResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SynthesizeSpeechResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SynthesizeSpeechResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> SynthesizeSpeechResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SynthesizeSpeechResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SynthesizeSpeechResponse -> m SynthesizeSpeechResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthesizeSpeechResponse -> m SynthesizeSpeechResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthesizeSpeechResponse -> m SynthesizeSpeechResponse #

Show SynthesizeSpeechResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Generic SynthesizeSpeechResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Associated Types

type Rep SynthesizeSpeechResponse :: Type -> Type #

ToJSON SynthesizeSpeechResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

FromJSON SynthesizeSpeechResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep SynthesizeSpeechResponse Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep SynthesizeSpeechResponse = D1 (MetaData "SynthesizeSpeechResponse" "Network.Google.TextToSpeech.Types.Product" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" True) (C1 (MetaCons "SynthesizeSpeechResponse'" PrefixI True) (S1 (MetaSel (Just "_ssrAudioContent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bytes))))

synthesizeSpeechResponse :: SynthesizeSpeechResponse Source #

Creates a value of SynthesizeSpeechResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ssrAudioContent :: Lens' SynthesizeSpeechResponse (Maybe ByteString) Source #

The audio data bytes encoded as specified in the request, including the header (For LINEAR16 audio, we include the WAV header). Note: as with all bytes fields, protobuffers use a pure binary representation, whereas JSON representations use base64.

Voice

data Voice Source #

Description of a voice supported by the TTS service.

See: voice smart constructor.

Instances
Eq Voice Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

(==) :: Voice -> Voice -> Bool #

(/=) :: Voice -> Voice -> Bool #

Data Voice Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Voice -> c Voice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Voice #

toConstr :: Voice -> Constr #

dataTypeOf :: Voice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Voice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Voice) #

gmapT :: (forall b. Data b => b -> b) -> Voice -> Voice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Voice -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Voice -> r #

gmapQ :: (forall d. Data d => d -> u) -> Voice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Voice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Voice -> m Voice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Voice -> m Voice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Voice -> m Voice #

Show Voice Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

Generic Voice Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

Associated Types

type Rep Voice :: Type -> Type #

Methods

from :: Voice -> Rep Voice x #

to :: Rep Voice x -> Voice #

ToJSON Voice Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

FromJSON Voice Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep Voice Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Product

type Rep Voice = D1 (MetaData "Voice" "Network.Google.TextToSpeech.Types.Product" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) (C1 (MetaCons "Voice'" PrefixI True) ((S1 (MetaSel (Just "_vLanguageCodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_vNATuralSampleRateHertz") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) :*: (S1 (MetaSel (Just "_vSsmlGender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VoiceSsmlGender)) :*: S1 (MetaSel (Just "_vName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

voice :: Voice Source #

Creates a value of Voice with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

vLanguageCodes :: Lens' Voice [Text] Source #

The languages that this voice supports, expressed as BCP-47 language tags (e.g. "en-US", "es-419", "cmn-tw").

vNATuralSampleRateHertz :: Lens' Voice (Maybe Int32) Source #

The natural sample rate (in hertz) for this voice.

vSsmlGender :: Lens' Voice (Maybe VoiceSsmlGender) Source #

The gender of this voice.

vName :: Lens' Voice (Maybe Text) Source #

The name of this voice. Each distinct voice has a unique name.

AudioConfigAudioEncoding

data AudioConfigAudioEncoding Source #

Required. The format of the requested audio byte stream.

Constructors

AudioEncodingUnspecified

AUDIO_ENCODING_UNSPECIFIED Not specified. Will return result google.rpc.Code.INVALID_ARGUMENT.

LINEAR16

LINEAR16 Uncompressed 16-bit signed little-endian samples (Linear PCM). Audio content returned as LINEAR16 also contains a WAV header.

MP3

MP3 MP3 audio.

OggOpus

OGG_OPUS Opus encoded audio wrapped in an ogg container. The result will be a file which can be played natively on Android, and in browsers (at least Chrome and Firefox). The quality of the encoding is considerably higher than MP3 while using approximately the same bitrate.

Instances
Enum AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Eq AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Data AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AudioConfigAudioEncoding -> c AudioConfigAudioEncoding #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AudioConfigAudioEncoding #

toConstr :: AudioConfigAudioEncoding -> Constr #

dataTypeOf :: AudioConfigAudioEncoding -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AudioConfigAudioEncoding) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AudioConfigAudioEncoding) #

gmapT :: (forall b. Data b => b -> b) -> AudioConfigAudioEncoding -> AudioConfigAudioEncoding #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AudioConfigAudioEncoding -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AudioConfigAudioEncoding -> r #

gmapQ :: (forall d. Data d => d -> u) -> AudioConfigAudioEncoding -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AudioConfigAudioEncoding -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AudioConfigAudioEncoding -> m AudioConfigAudioEncoding #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioConfigAudioEncoding -> m AudioConfigAudioEncoding #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioConfigAudioEncoding -> m AudioConfigAudioEncoding #

Ord AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Read AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Show AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Generic AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

Associated Types

type Rep AudioConfigAudioEncoding :: Type -> Type #

Hashable AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

ToJSON AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromJSON AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

FromHttpApiData AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

ToHttpApiData AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep AudioConfigAudioEncoding Source # 
Instance details

Defined in Network.Google.TextToSpeech.Types.Sum

type Rep AudioConfigAudioEncoding = D1 (MetaData "AudioConfigAudioEncoding" "Network.Google.TextToSpeech.Types.Sum" "gogol-texttospeech-0.4.0-1tOSifr1Iss9wmHJGn31FK" False) ((C1 (MetaCons "AudioEncodingUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LINEAR16" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MP3" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OggOpus" PrefixI False) (U1 :: Type -> Type)))