amazonka-polly-1.6.1: Amazon Polly SDK.

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

Network.AWS.Polly.Types

Contents

Description

 
Synopsis

Service Configuration

polly :: Service Source #

API version 2016-06-10 of the Amazon Polly SDK configuration.

Errors

_UnsupportedPlsLanguageException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The language specified in the lexicon is unsupported. For a list of supported languages, see Lexicon Attributes .

_InvalidSsmlException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The SSML you provided is invalid. Verify the SSML syntax, spelling of tags and values, and then try again.

_InvalidSampleRateException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified sample rate is not valid.

_MaxLexiconsNumberExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The maximum number of lexicons would be exceeded by this operation.

_TextLengthExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The value of the Text parameter is longer than the accepted limits. The limit for input text is a maximum of 3000 characters total, of which no more than 1500 can be billed characters. SSML tags are not counted as billed characters.

_MaxLexemeLengthExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The maximum size of the lexeme would be exceeded by this operation.

_InvalidLexiconException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Amazon Polly can't find the specified lexicon. Verify that the lexicon's name is spelled correctly, and then try again.

_ServiceFailureException :: AsError a => Getting (First ServiceError) a ServiceError Source #

An unknown condition has caused a service failure.

_UnsupportedPlsAlphabetException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The alphabet specified by the lexicon is not a supported alphabet. Valid values are x-sampa and ipa .

_InvalidNextTokenException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The NextToken is invalid. Verify that it's spelled correctly, and then try again.

_MarksNotSupportedForFormatException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Speech marks are not supported for the OutputFormat selected. Speech marks are only available for content in json format.

_SsmlMarksNotSupportedForTextTypeException :: AsError a => Getting (First ServiceError) a ServiceError Source #

SSML speech marks are not supported for plain text-type input.

_LexiconSizeExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The maximum size of the specified lexicon would be exceeded by this operation.

_LexiconNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Amazon Polly can't find the specified lexicon. This could be caused by a lexicon that is missing, its name is misspelled or specifying a lexicon that is in a different region.

Verify that the lexicon exists, is in the region (see ListLexicons ) and that you spelled its name is spelled correctly. Then try again.

Gender

data Gender Source #

Constructors

Female 
Male 
Instances
Bounded Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Enum Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Eq Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

Data Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

toConstr :: Gender -> Constr #

dataTypeOf :: Gender -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Read Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Show Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Generic Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Associated Types

type Rep Gender :: Type -> Type #

Methods

from :: Gender -> Rep Gender x #

to :: Rep Gender x -> Gender #

Hashable Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

hashWithSalt :: Int -> Gender -> Int #

hash :: Gender -> Int #

FromJSON Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToHeader Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toHeader :: HeaderName -> Gender -> [Header] #

ToQuery Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToByteString Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toBS :: Gender -> ByteString #

FromText Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

parser :: Parser Gender #

ToText Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toText :: Gender -> Text #

NFData Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

rnf :: Gender -> () #

type Rep Gender Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

type Rep Gender = D1 (MetaData "Gender" "Network.AWS.Polly.Types.Sum" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) (C1 (MetaCons "Female" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Male" PrefixI False) (U1 :: Type -> Type))

LanguageCode

data LanguageCode Source #

Instances
Bounded LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Enum LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Eq LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Data LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

toConstr :: LanguageCode -> Constr #

dataTypeOf :: LanguageCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Read LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Show LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Generic LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Associated Types

type Rep LanguageCode :: Type -> Type #

Hashable LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToJSON LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

FromJSON LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToHeader LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToQuery LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToByteString LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

FromText LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToText LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toText :: LanguageCode -> Text #

NFData LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

rnf :: LanguageCode -> () #

type Rep LanguageCode Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

type Rep LanguageCode = D1 (MetaData "LanguageCode" "Network.AWS.Polly.Types.Sum" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) ((((C1 (MetaCons "CyGb" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DaDk" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DeDe" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "EnAu" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EnGb" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EnGbWls" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "EnIn" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EnUs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EsEs" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "EsUs" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FrCa" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FrFr" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "IsIs" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ItIt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JaJp" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "KoKr" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NbNo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NlNl" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "PlPl" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PtBr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PtPt" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "RoRo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RuRu" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SvSe" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TrTr" PrefixI False) (U1 :: Type -> Type))))))

OutputFormat

data OutputFormat Source #

Constructors

JSON 
MP3 
OggVorbis 
Pcm 
Instances
Bounded OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Enum OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Eq OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Data OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

toConstr :: OutputFormat -> Constr #

dataTypeOf :: OutputFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Read OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Show OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Generic OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Associated Types

type Rep OutputFormat :: Type -> Type #

Hashable OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToJSON OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToHeader OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToQuery OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToByteString OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

FromText OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToText OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toText :: OutputFormat -> Text #

NFData OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

rnf :: OutputFormat -> () #

type Rep OutputFormat Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

type Rep OutputFormat = D1 (MetaData "OutputFormat" "Network.AWS.Polly.Types.Sum" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) ((C1 (MetaCons "JSON" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MP3" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OggVorbis" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Pcm" PrefixI False) (U1 :: Type -> Type)))

SpeechMarkType

data SpeechMarkType Source #

Constructors

Sentence 
Ssml 
Viseme 
Word 
Instances
Bounded SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Enum SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Eq SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Data SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

toConstr :: SpeechMarkType -> Constr #

dataTypeOf :: SpeechMarkType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Read SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Show SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Generic SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Associated Types

type Rep SpeechMarkType :: Type -> Type #

Hashable SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToJSON SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToHeader SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToQuery SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToByteString SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

FromText SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToText SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

NFData SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

rnf :: SpeechMarkType -> () #

type Rep SpeechMarkType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

type Rep SpeechMarkType = D1 (MetaData "SpeechMarkType" "Network.AWS.Polly.Types.Sum" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) ((C1 (MetaCons "Sentence" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ssml" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Viseme" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Word" PrefixI False) (U1 :: Type -> Type)))

TextType

data TextType Source #

Constructors

TTSsml 
TTText 
Instances
Bounded TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Enum TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Eq TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Data TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

toConstr :: TextType -> Constr #

dataTypeOf :: TextType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Read TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Show TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Generic TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Associated Types

type Rep TextType :: Type -> Type #

Methods

from :: TextType -> Rep TextType x #

to :: Rep TextType x -> TextType #

Hashable TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

hashWithSalt :: Int -> TextType -> Int #

hash :: TextType -> Int #

ToJSON TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToHeader TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toHeader :: HeaderName -> TextType -> [Header] #

ToQuery TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToByteString TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toBS :: TextType -> ByteString #

FromText TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToText TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toText :: TextType -> Text #

NFData TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

rnf :: TextType -> () #

type Rep TextType Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

type Rep TextType = D1 (MetaData "TextType" "Network.AWS.Polly.Types.Sum" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) (C1 (MetaCons "TTSsml" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TTText" PrefixI False) (U1 :: Type -> Type))

VoiceId

data VoiceId Source #

Instances
Bounded VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Enum VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Eq VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

Data VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

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

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

toConstr :: VoiceId -> Constr #

dataTypeOf :: VoiceId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Read VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Show VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Generic VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Associated Types

type Rep VoiceId :: Type -> Type #

Methods

from :: VoiceId -> Rep VoiceId x #

to :: Rep VoiceId x -> VoiceId #

Hashable VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

hashWithSalt :: Int -> VoiceId -> Int #

hash :: VoiceId -> Int #

ToJSON VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

FromJSON VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToHeader VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toHeader :: HeaderName -> VoiceId -> [Header] #

ToQuery VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToByteString VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toBS :: VoiceId -> ByteString #

FromText VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

ToText VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

toText :: VoiceId -> Text #

NFData VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

Methods

rnf :: VoiceId -> () #

type Rep VoiceId Source # 
Instance details

Defined in Network.AWS.Polly.Types.Sum

type Rep VoiceId = D1 (MetaData "VoiceId" "Network.AWS.Polly.Types.Sum" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) (((((C1 (MetaCons "Aditi" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Amy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Astrid" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Brian" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Carla" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Carmen" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Celine" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Chantal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Conchita" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Cristiano" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Dora" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Emma" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Enrique" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "Ewa" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Filiz" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Geraint" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Giorgio" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Gwyneth" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Hans" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Ines" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ivy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Jacek" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Jan" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Joanna" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Joey" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Justin" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "Karl" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Kendra" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Kimberly" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Liv" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Lotte" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mads" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Maja" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Marlene" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mathieu" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Matthew" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Maxim" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Miguel" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mizuki" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "Naja" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Nicole" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Penelope" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Raveena" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ricardo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ruben" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Russell" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Salli" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Seoyeon" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Takumi" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Tatyana" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Vicki" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Vitoria" PrefixI False) (U1 :: Type -> Type)))))))

Lexicon

data Lexicon Source #

Provides lexicon name and lexicon content in string format. For more information, see Pronunciation Lexicon Specification (PLS) Version 1.0 .

See: lexicon smart constructor.

Instances
Eq Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

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

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

Data Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

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

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

toConstr :: Lexicon -> Constr #

dataTypeOf :: Lexicon -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Generic Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Associated Types

type Rep Lexicon :: Type -> Type #

Methods

from :: Lexicon -> Rep Lexicon x #

to :: Rep Lexicon x -> Lexicon #

Hashable Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

hashWithSalt :: Int -> Lexicon -> Int #

hash :: Lexicon -> Int #

FromJSON Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

NFData Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

rnf :: Lexicon -> () #

type Rep Lexicon Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

type Rep Lexicon = D1 (MetaData "Lexicon" "Network.AWS.Polly.Types.Product" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) (C1 (MetaCons "Lexicon'" PrefixI True) (S1 (MetaSel (Just "_lContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Sensitive Text)))))

lexicon :: Lexicon Source #

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

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

  • lContent - Lexicon content in string format. The content of a lexicon must be in PLS format.
  • lName - Name of the lexicon.

lContent :: Lens' Lexicon (Maybe Text) Source #

Lexicon content in string format. The content of a lexicon must be in PLS format.

lName :: Lens' Lexicon (Maybe Text) Source #

Name of the lexicon.

LexiconAttributes

data LexiconAttributes Source #

Contains metadata describing the lexicon such as the number of lexemes, language code, and so on. For more information, see Managing Lexicons .

See: lexiconAttributes smart constructor.

Instances
Eq LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Data LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

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

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

toConstr :: LexiconAttributes -> Constr #

dataTypeOf :: LexiconAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Show LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Generic LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Associated Types

type Rep LexiconAttributes :: Type -> Type #

Hashable LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

FromJSON LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

NFData LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

rnf :: LexiconAttributes -> () #

type Rep LexiconAttributes Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

type Rep LexiconAttributes = D1 (MetaData "LexiconAttributes" "Network.AWS.Polly.Types.Product" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) (C1 (MetaCons "LexiconAttributes'" PrefixI True) ((S1 (MetaSel (Just "_laLanguageCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LanguageCode)) :*: (S1 (MetaSel (Just "_laSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_laLexemesCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) :*: (S1 (MetaSel (Just "_laLexiconARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_laAlphabet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_laLastModified") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))))))

lexiconAttributes :: LexiconAttributes Source #

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

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

  • laLanguageCode - Language code that the lexicon applies to. A lexicon with a language code such as "en" would be applied to all English languages (en-GB, en-US, en-AUS, en-WLS, and so on.
  • laSize - Total size of the lexicon, in characters.
  • laLexemesCount - Number of lexemes in the lexicon.
  • laLexiconARN - Amazon Resource Name (ARN) of the lexicon.
  • laAlphabet - Phonetic alphabet used in the lexicon. Valid values are ipa and x-sampa .
  • laLastModified - Date lexicon was last modified (a timestamp value).

laLanguageCode :: Lens' LexiconAttributes (Maybe LanguageCode) Source #

Language code that the lexicon applies to. A lexicon with a language code such as "en" would be applied to all English languages (en-GB, en-US, en-AUS, en-WLS, and so on.

laSize :: Lens' LexiconAttributes (Maybe Int) Source #

Total size of the lexicon, in characters.

laLexemesCount :: Lens' LexiconAttributes (Maybe Int) Source #

Number of lexemes in the lexicon.

laLexiconARN :: Lens' LexiconAttributes (Maybe Text) Source #

Amazon Resource Name (ARN) of the lexicon.

laAlphabet :: Lens' LexiconAttributes (Maybe Text) Source #

Phonetic alphabet used in the lexicon. Valid values are ipa and x-sampa .

laLastModified :: Lens' LexiconAttributes (Maybe UTCTime) Source #

Date lexicon was last modified (a timestamp value).

LexiconDescription

data LexiconDescription Source #

Describes the content of the lexicon.

See: lexiconDescription smart constructor.

Instances
Eq LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Data LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

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

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

toConstr :: LexiconDescription -> Constr #

dataTypeOf :: LexiconDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Generic LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Associated Types

type Rep LexiconDescription :: Type -> Type #

Hashable LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

FromJSON LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

NFData LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

rnf :: LexiconDescription -> () #

type Rep LexiconDescription Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

type Rep LexiconDescription = D1 (MetaData "LexiconDescription" "Network.AWS.Polly.Types.Product" "amazonka-polly-1.6.1-F2G7y4pa5Zy7tjUQirknXR" False) (C1 (MetaCons "LexiconDescription'" PrefixI True) (S1 (MetaSel (Just "_ldAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LexiconAttributes)) :*: S1 (MetaSel (Just "_ldName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Sensitive Text)))))

lexiconDescription :: LexiconDescription Source #

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

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

ldName :: Lens' LexiconDescription (Maybe Text) Source #

Name of the lexicon.

Voice

data Voice Source #

Description of the voice.

See: voice smart constructor.

Instances
Eq Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

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

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

Data Voice Source # 
Instance details

Defined in Network.AWS.Polly.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 #

Read Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Show Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

Generic Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Associated Types

type Rep Voice :: Type -> Type #

Methods

from :: Voice -> Rep Voice x #

to :: Rep Voice x -> Voice #

Hashable Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

hashWithSalt :: Int -> Voice -> Int #

hash :: Voice -> Int #

FromJSON Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

NFData Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

Methods

rnf :: Voice -> () #

type Rep Voice Source # 
Instance details

Defined in Network.AWS.Polly.Types.Product

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:

  • vLanguageCode - Language code of the voice.
  • vLanguageName - Human readable name of the language in English.
  • vGender - Gender of the voice.
  • vName - Name of the voice (for example, Salli, Kendra, etc.). This provides a human readable voice name that you might display in your application.
  • vId - Amazon Polly assigned voice ID. This is the ID that you specify when calling the SynthesizeSpeech operation.

vLanguageCode :: Lens' Voice (Maybe LanguageCode) Source #

Language code of the voice.

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

Human readable name of the language in English.

vGender :: Lens' Voice (Maybe Gender) Source #

Gender of the voice.

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

Name of the voice (for example, Salli, Kendra, etc.). This provides a human readable voice name that you might display in your application.

vId :: Lens' Voice (Maybe VoiceId) Source #

Amazon Polly assigned voice ID. This is the ID that you specify when calling the SynthesizeSpeech operation.