gogol-speech-0.4.0: Google Cloud 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.Speech

Contents

Description

Converts audio to text by applying powerful neural network models.

See: Cloud Speech API Reference

Synopsis

Service Configuration

speechService :: ServiceConfig Source #

Default request referring to version v1p1beta1 of the Cloud 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

API Declaration

Resources

speech.operations.get

speech.operations.list

speech.projects.locations.operations.get

speech.projects.locations.operations.list

speech.projects.operations.manualRecognitionTasks.get

speech.speech.longrunningrecognize

speech.speech.recognize

Types

LongRunningRecognizeMetadata

data LongRunningRecognizeMetadata Source #

Describes the progress of a long-running `LongRunningRecognize` call. It is included in the `metadata` field of the `Operation` returned by the `GetOperation` call of the `google::longrunning::Operations` service.

See: longRunningRecognizeMetadata smart constructor.

Instances
Eq LongRunningRecognizeMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data LongRunningRecognizeMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: LongRunningRecognizeMetadata -> Constr #

dataTypeOf :: LongRunningRecognizeMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LongRunningRecognizeMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic LongRunningRecognizeMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep LongRunningRecognizeMetadata :: Type -> Type #

ToJSON LongRunningRecognizeMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON LongRunningRecognizeMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep LongRunningRecognizeMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep LongRunningRecognizeMetadata = D1 (MetaData "LongRunningRecognizeMetadata" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "LongRunningRecognizeMetadata'" PrefixI True) (S1 (MetaSel (Just "_lrrmStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: (S1 (MetaSel (Just "_lrrmProgressPercent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_lrrmLastUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')))))

longRunningRecognizeMetadata :: LongRunningRecognizeMetadata Source #

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

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

lrrmStartTime :: Lens' LongRunningRecognizeMetadata (Maybe UTCTime) Source #

Time when the request was received.

lrrmProgressPercent :: Lens' LongRunningRecognizeMetadata (Maybe Int32) Source #

Approximate percentage of audio processed thus far. Guaranteed to be 100 when the audio is fully processed and the results are available.

lrrmLastUpdateTime :: Lens' LongRunningRecognizeMetadata (Maybe UTCTime) Source #

Time of the most recent processing update.

Status

data Status Source #

The `Status` type defines a logical error model that is suitable for different programming environments, including REST APIs and RPC APIs. It is used by gRPC. The error model is designed to be: - Simple to use and understand for most users - Flexible enough to meet unexpected needs # Overview The `Status` message contains three pieces of data: error code, error message, and error details. The error code should be an enum value of google.rpc.Code, but it may accept additional error codes if needed. The error message should be a developer-facing English message that helps developers *understand* and *resolve* the error. If a localized user-facing error message is needed, put the localized message in the error details or localize it in the client. The optional error details may contain arbitrary information about the error. There is a predefined set of error detail types in the package `google.rpc` that can be used for common error conditions. # Language mapping The `Status` message is the logical representation of the error model, but it is not necessarily the actual wire format. When the `Status` message is exposed in different client libraries and different wire protocols, it can be mapped differently. For example, it will likely be mapped to some exceptions in Java, but more likely mapped to some error codes in C. # Other uses The error model and the `Status` message can be used in a variety of environments, either with or without APIs, to provide a consistent developer experience across different environments. Example uses of this error model include: - Partial errors. If a service needs to return partial errors to the client, it may embed the `Status` in the normal response to indicate the partial errors. - Workflow errors. A typical workflow has multiple steps. Each step may have a `Status` message for error reporting. - Batch operations. If a client uses batch request and batch response, the `Status` message should be used directly inside batch response, one for each error sub-response. - Asynchronous operations. If an API call embeds asynchronous operation results in its response, the status of those operations should be represented directly using the `Status` message. - Logging. If some API errors are stored in logs, the message `Status` could be used directly after any stripping needed for security/privacy reasons.

See: status smart constructor.

Instances
Eq Status Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

Data Status Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Status Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic Status Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON Status Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep Status Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep Status = D1 (MetaData "Status" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "Status'" PrefixI True) (S1 (MetaSel (Just "_sDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StatusDetailsItem])) :*: (S1 (MetaSel (Just "_sCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_sMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

status :: Status Source #

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

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

sDetails :: Lens' Status [StatusDetailsItem] Source #

A list of messages that carry the error details. There is a common set of message types for APIs to use.

sCode :: Lens' Status (Maybe Int32) Source #

The status code, which should be an enum value of google.rpc.Code.

sMessage :: Lens' Status (Maybe Text) Source #

A developer-facing error message, which should be in English. Any user-facing error message should be localized and sent in the google.rpc.Status.details field, or localized by the client.

SpeechContext

data SpeechContext Source #

Provides "hints" to the speech recognizer to favor specific words and phrases in the results.

See: speechContext smart constructor.

Instances
Eq SpeechContext Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data SpeechContext Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: SpeechContext -> Constr #

dataTypeOf :: SpeechContext -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpeechContext Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic SpeechContext Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep SpeechContext :: Type -> Type #

ToJSON SpeechContext Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON SpeechContext Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeechContext Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeechContext = D1 (MetaData "SpeechContext" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" True) (C1 (MetaCons "SpeechContext'" PrefixI True) (S1 (MetaSel (Just "_scPhrases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

speechContext :: SpeechContext Source #

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

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

scPhrases :: Lens' SpeechContext [Text] Source #

  • Optional* A list of strings containing words and phrases "hints" so that the speech recognition is more likely to recognize them. This can be used to improve the accuracy for specific words and phrases, for example, if specific commands are typically spoken by the user. This can also be used to add additional words to the vocabulary of the recognizer. See usage limits.

RecognitionMetadataOriginalMediaType

data RecognitionMetadataOriginalMediaType Source #

The original media the speech was recorded on.

Constructors

OriginalMediaTypeUnspecified

ORIGINAL_MEDIA_TYPE_UNSPECIFIED Unknown original media type.

Audio

AUDIO The speech data is an audio recording.

Video

VIDEO The speech data originally recorded on a video.

Instances
Enum RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Eq RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Data RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Methods

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

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

toConstr :: RecognitionMetadataOriginalMediaType -> Constr #

dataTypeOf :: RecognitionMetadataOriginalMediaType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Read RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Show RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Generic RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Hashable RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToJSON RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromJSON RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromHttpApiData RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToHttpApiData RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataOriginalMediaType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataOriginalMediaType = D1 (MetaData "RecognitionMetadataOriginalMediaType" "Network.Google.Speech.Types.Sum" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "OriginalMediaTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Audio" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Video" PrefixI False) (U1 :: Type -> Type)))

ListOperationsResponse

data ListOperationsResponse Source #

The response message for Operations.ListOperations.

See: listOperationsResponse smart constructor.

Instances
Eq ListOperationsResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data ListOperationsResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: ListOperationsResponse -> Constr #

dataTypeOf :: ListOperationsResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListOperationsResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic ListOperationsResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep ListOperationsResponse :: Type -> Type #

ToJSON ListOperationsResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON ListOperationsResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep ListOperationsResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep ListOperationsResponse = D1 (MetaData "ListOperationsResponse" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "ListOperationsResponse'" PrefixI True) (S1 (MetaSel (Just "_lorNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lorOperations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Operation]))))

listOperationsResponse :: ListOperationsResponse Source #

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

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

lorNextPageToken :: Lens' ListOperationsResponse (Maybe Text) Source #

The standard List next-page token.

lorOperations :: Lens' ListOperationsResponse [Operation] Source #

A list of operations that matches the specified filter in the request.

RecognitionMetadata

data RecognitionMetadata Source #

Description of audio data to be recognized.

See: recognitionMetadata smart constructor.

Instances
Eq RecognitionMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data RecognitionMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: RecognitionMetadata -> Constr #

dataTypeOf :: RecognitionMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RecognitionMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic RecognitionMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep RecognitionMetadata :: Type -> Type #

ToJSON RecognitionMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON RecognitionMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognitionMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

rmAudioTopic :: Lens' RecognitionMetadata (Maybe Text) Source #

Description of the content. Eg. "Recordings of federal supreme court hearings from 2012".

rmInteractionType :: Lens' RecognitionMetadata (Maybe RecognitionMetadataInteractionType) Source #

The use case most closely describing the audio content to be recognized.

rmOriginalMimeType :: Lens' RecognitionMetadata (Maybe Text) Source #

Mime type of the original audio file. For example `audio/m4a`, `audio/x-alaw-basic`, `audio/mp3`, `audio/3gpp`. A list of possible audio mime types is maintained at http://www.iana.org/assignments/media-types/media-types.xhtml#audio

rmIndustryNaicsCodeOfAudio :: Lens' RecognitionMetadata (Maybe Word32) Source #

The industry vertical to which this speech recognition request most closely applies. This is most indicative of the topics contained in the audio. Use the 6-digit NAICS code to identify the industry vertical - see https://www.naics.com/search/.

rmObfuscatedId :: Lens' RecognitionMetadata (Maybe Int64) Source #

Obfuscated (privacy-protected) ID of the user, to identify number of unique users using the service.

rmRecordingDeviceName :: Lens' RecognitionMetadata (Maybe Text) Source #

The device used to make the recording. Examples 'Nexus 5X' or 'Polycom SoundStation IP 6000' or 'POTS' or 'VoIP' or 'Cardioid Microphone'.

rmMicrophoneDistance :: Lens' RecognitionMetadata (Maybe RecognitionMetadataMicrophoneDistance) Source #

The audio type that most closely describes the audio being recognized.

RecognizeRequest

data RecognizeRequest Source #

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

See: recognizeRequest smart constructor.

Instances
Eq RecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data RecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: RecognizeRequest -> Constr #

dataTypeOf :: RecognizeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic RecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep RecognizeRequest :: Type -> Type #

ToJSON RecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON RecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognizeRequest = D1 (MetaData "RecognizeRequest" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "RecognizeRequest'" PrefixI True) (S1 (MetaSel (Just "_rrConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecognitionConfig)) :*: S1 (MetaSel (Just "_rrAudio") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecognitionAudio))))

recognizeRequest :: RecognizeRequest Source #

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

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

rrConfig :: Lens' RecognizeRequest (Maybe RecognitionConfig) Source #

  • Required* Provides information to the recognizer that specifies how to process the request.

rrAudio :: Lens' RecognizeRequest (Maybe RecognitionAudio) Source #

  • Required* The audio data to be recognized.

Operation

data Operation Source #

This resource represents a long-running operation that is the result of a network API call.

See: operation smart constructor.

Instances
Eq Operation Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data Operation Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: Operation -> Constr #

dataTypeOf :: Operation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Operation Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic Operation Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep Operation :: Type -> Type #

ToJSON Operation Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON Operation Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep Operation Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

operation :: Operation Source #

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

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

oDone :: Lens' Operation (Maybe Bool) Source #

If the value is `false`, it means the operation is still in progress. If `true`, the operation is completed, and either `error` or `response` is available.

oError :: Lens' Operation (Maybe Status) Source #

The error result of the operation in case of failure or cancellation.

oResponse :: Lens' Operation (Maybe OperationResponse) Source #

The normal response of the operation in case of success. If the original method returns no data on success, such as `Delete`, the response is `google.protobuf.Empty`. If the original method is standard `Get`/`Create`/`Update`, the response should be the resource. For other methods, the response should have the type `XxxResponse`, where `Xxx` is the original method name. For example, if the original method name is `TakeSnapshot()`, the inferred response type is `TakeSnapshotResponse`.

oName :: Lens' Operation (Maybe Text) Source #

The server-assigned name, which is only unique within the same service that originally returns it. If you use the default HTTP mapping, the `name` should have the format of `operations/some/unique/name`.

oMetadata :: Lens' Operation (Maybe OperationMetadata) Source #

Service-specific metadata associated with the operation. It typically contains progress information and common metadata such as create time. Some services might not provide such metadata. Any method that returns a long-running operation should document the metadata type, if any.

SpeechRecognitionAlternative

data SpeechRecognitionAlternative Source #

Alternative hypotheses (a.k.a. n-best list).

See: speechRecognitionAlternative smart constructor.

Instances
Eq SpeechRecognitionAlternative Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data SpeechRecognitionAlternative Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: SpeechRecognitionAlternative -> Constr #

dataTypeOf :: SpeechRecognitionAlternative -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpeechRecognitionAlternative Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic SpeechRecognitionAlternative Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep SpeechRecognitionAlternative :: Type -> Type #

ToJSON SpeechRecognitionAlternative Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON SpeechRecognitionAlternative Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeechRecognitionAlternative Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeechRecognitionAlternative = D1 (MetaData "SpeechRecognitionAlternative" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "SpeechRecognitionAlternative'" PrefixI True) (S1 (MetaSel (Just "_sraConfidence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: (S1 (MetaSel (Just "_sraWords") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [WordInfo])) :*: S1 (MetaSel (Just "_sraTranscript") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

speechRecognitionAlternative :: SpeechRecognitionAlternative Source #

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

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

sraConfidence :: Lens' SpeechRecognitionAlternative (Maybe Double) Source #

Output only. The confidence estimate between 0.0 and 1.0. A higher number indicates an estimated greater likelihood that the recognized words are correct. This field is set only for the top alternative of a non-streaming result or, of a streaming result where `is_final=true`. This field is not guaranteed to be accurate and users should not rely on it to be always provided. The default of 0.0 is a sentinel value indicating `confidence` was not set.

sraWords :: Lens' SpeechRecognitionAlternative [WordInfo] Source #

Output only. A list of word-specific information for each recognized word. Note: When `enable_speaker_diarization` is true, you will see all the words from the beginning of the audio.

sraTranscript :: Lens' SpeechRecognitionAlternative (Maybe Text) Source #

Output only. Transcript text representing the words that the user spoke.

WordInfo

data WordInfo Source #

Word-specific information for recognized words.

See: wordInfo smart constructor.

Instances
Eq WordInfo Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data WordInfo Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: WordInfo -> Constr #

dataTypeOf :: WordInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show WordInfo Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic WordInfo Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep WordInfo :: Type -> Type #

Methods

from :: WordInfo -> Rep WordInfo x #

to :: Rep WordInfo x -> WordInfo #

ToJSON WordInfo Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON WordInfo Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep WordInfo Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep WordInfo = D1 (MetaData "WordInfo" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "WordInfo'" PrefixI True) ((S1 (MetaSel (Just "_wiStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GDuration)) :*: S1 (MetaSel (Just "_wiConfidence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) :*: (S1 (MetaSel (Just "_wiEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GDuration)) :*: (S1 (MetaSel (Just "_wiWord") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_wiSpeakerTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

wordInfo :: WordInfo Source #

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

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

wiStartTime :: Lens' WordInfo (Maybe Scientific) Source #

Output only. Time offset relative to the beginning of the audio, and corresponding to the start of the spoken word. This field is only set if `enable_word_time_offsets=true` and only in the top hypothesis. This is an experimental feature and the accuracy of the time offset can vary.

wiConfidence :: Lens' WordInfo (Maybe Double) Source #

Output only. The confidence estimate between 0.0 and 1.0. A higher number indicates an estimated greater likelihood that the recognized words are correct. This field is set only for the top alternative of a non-streaming result or, of a streaming result where `is_final=true`. This field is not guaranteed to be accurate and users should not rely on it to be always provided. The default of 0.0 is a sentinel value indicating `confidence` was not set.

wiEndTime :: Lens' WordInfo (Maybe Scientific) Source #

Output only. Time offset relative to the beginning of the audio, and corresponding to the end of the spoken word. This field is only set if `enable_word_time_offsets=true` and only in the top hypothesis. This is an experimental feature and the accuracy of the time offset can vary.

wiWord :: Lens' WordInfo (Maybe Text) Source #

Output only. The word corresponding to this set of information.

wiSpeakerTag :: Lens' WordInfo (Maybe Int32) Source #

Output only. A distinct integer value is assigned for every speaker within the audio. This field specifies which one of those speakers was detected to have spoken this word. Value ranges from '1' to diarization_speaker_count. speaker_tag is set if enable_speaker_diarization = 'true' and only in the top alternative.

RecognitionMetadataInteractionType

data RecognitionMetadataInteractionType Source #

The use case most closely describing the audio content to be recognized.

Constructors

InteractionTypeUnspecified

INTERACTION_TYPE_UNSPECIFIED Use case is either unknown or is something other than one of the other values below.

Discussion

DISCUSSION Multiple people in a conversation or discussion. For example in a meeting with two or more people actively participating. Typically all the primary people speaking would be in the same room (if not, see PHONE_CALL)

Presentation

PRESENTATION One or more persons lecturing or presenting to others, mostly uninterrupted.

PhoneCall

PHONE_CALL A phone-call or video-conference in which two or more people, who are not in the same room, are actively participating.

Voicemail

VOICEMAIL A recorded message intended for another person to listen to.

ProfessionallyProduced

PROFESSIONALLY_PRODUCED Professionally produced audio (eg. TV Show, Podcast).

VoiceSearch

VOICE_SEARCH Transcribe spoken questions and queries into text.

VoiceCommand

VOICE_COMMAND Transcribe voice commands, such as for controlling a device.

Dictation

DICTATION Transcribe speech to text to create a written document, such as a text-message, email or report.

Instances
Enum RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Eq RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Data RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Methods

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

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

toConstr :: RecognitionMetadataInteractionType -> Constr #

dataTypeOf :: RecognitionMetadataInteractionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Read RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Show RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Generic RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Associated Types

type Rep RecognitionMetadataInteractionType :: Type -> Type #

Hashable RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToJSON RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromJSON RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromHttpApiData RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToHttpApiData RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataInteractionType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataInteractionType = D1 (MetaData "RecognitionMetadataInteractionType" "Network.Google.Speech.Types.Sum" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (((C1 (MetaCons "InteractionTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Discussion" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Presentation" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PhoneCall" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Voicemail" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProfessionallyProduced" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VoiceSearch" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "VoiceCommand" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Dictation" PrefixI False) (U1 :: Type -> Type)))))

StatusDetailsItem

data StatusDetailsItem Source #

Instances
Eq StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: StatusDetailsItem -> Constr #

dataTypeOf :: StatusDetailsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep StatusDetailsItem :: Type -> Type #

ToJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep StatusDetailsItem = D1 (MetaData "StatusDetailsItem" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" True) (C1 (MetaCons "StatusDetailsItem'" PrefixI True) (S1 (MetaSel (Just "_sdiAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

statusDetailsItem Source #

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

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

sdiAddtional :: Lens' StatusDetailsItem (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

SpeechRecognitionResult

data SpeechRecognitionResult Source #

A speech recognition result corresponding to a portion of the audio.

See: speechRecognitionResult smart constructor.

Instances
Eq SpeechRecognitionResult Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data SpeechRecognitionResult Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: SpeechRecognitionResult -> Constr #

dataTypeOf :: SpeechRecognitionResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpeechRecognitionResult Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic SpeechRecognitionResult Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep SpeechRecognitionResult :: Type -> Type #

ToJSON SpeechRecognitionResult Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON SpeechRecognitionResult Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeechRecognitionResult Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeechRecognitionResult = D1 (MetaData "SpeechRecognitionResult" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "SpeechRecognitionResult'" PrefixI True) (S1 (MetaSel (Just "_srrAlternatives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SpeechRecognitionAlternative])) :*: (S1 (MetaSel (Just "_srrLanguageCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_srrChannelTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

speechRecognitionResult :: SpeechRecognitionResult Source #

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

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

srrAlternatives :: Lens' SpeechRecognitionResult [SpeechRecognitionAlternative] Source #

Output only. May contain one or more recognition hypotheses (up to the maximum specified in `max_alternatives`). These alternatives are ordered in terms of accuracy, with the top (first) alternative being the most probable, as ranked by the recognizer.

srrLanguageCode :: Lens' SpeechRecognitionResult (Maybe Text) Source #

Output only. The BCP-47 language tag of the language in this result. This language code was detected to have the most likelihood of being spoken in the audio.

srrChannelTag :: Lens' SpeechRecognitionResult (Maybe Int32) Source #

For multi-channel audio, this is the channel number corresponding to the recognized result for the audio from that channel. For audio_channel_count = N, its output values can range from '1' to 'N'.

RecognitionAudio

data RecognitionAudio Source #

Contains audio data in the encoding specified in the `RecognitionConfig`. Either `content` or `uri` must be supplied. Supplying both or neither returns google.rpc.Code.INVALID_ARGUMENT. See content limits.

See: recognitionAudio smart constructor.

Instances
Eq RecognitionAudio Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data RecognitionAudio Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: RecognitionAudio -> Constr #

dataTypeOf :: RecognitionAudio -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RecognitionAudio Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic RecognitionAudio Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep RecognitionAudio :: Type -> Type #

ToJSON RecognitionAudio Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON RecognitionAudio Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognitionAudio Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognitionAudio = D1 (MetaData "RecognitionAudio" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "RecognitionAudio'" PrefixI True) (S1 (MetaSel (Just "_raURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_raContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes))))

recognitionAudio :: RecognitionAudio Source #

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

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

raURI :: Lens' RecognitionAudio (Maybe Text) Source #

URI that points to a file that contains audio data bytes as specified in `RecognitionConfig`. The file must not be compressed (for example, gzip). Currently, only Google Cloud Storage URIs are supported, which must be specified in the following format: `gs://bucket_name/object_name` (other URI formats return google.rpc.Code.INVALID_ARGUMENT). For more information, see Request URIs.

raContent :: Lens' RecognitionAudio (Maybe ByteString) Source #

The audio data bytes encoded as specified in `RecognitionConfig`. Note: as with all bytes fields, protobuffers use a pure binary representation, whereas JSON representations use base64.

RecognizeResponse

data RecognizeResponse Source #

The only message returned to the client by the `Recognize` method. It contains the result as zero or more sequential `SpeechRecognitionResult` messages.

See: recognizeResponse smart constructor.

Instances
Eq RecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data RecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: RecognizeResponse -> Constr #

dataTypeOf :: RecognizeResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic RecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep RecognizeResponse :: Type -> Type #

ToJSON RecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON RecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognizeResponse = D1 (MetaData "RecognizeResponse" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" True) (C1 (MetaCons "RecognizeResponse'" PrefixI True) (S1 (MetaSel (Just "_rrResults") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [SpeechRecognitionResult]))))

recognizeResponse :: RecognizeResponse Source #

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

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

rrResults :: Lens' RecognizeResponse [SpeechRecognitionResult] Source #

Output only. Sequential list of transcription results corresponding to sequential portions of audio.

RecognitionMetadataRecordingDeviceType

data RecognitionMetadataRecordingDeviceType Source #

The type of device the speech was recorded with.

Constructors

RecordingDeviceTypeUnspecified

RECORDING_DEVICE_TYPE_UNSPECIFIED The recording device is unknown.

Smartphone

SMARTPHONE Speech was recorded on a smartphone.

PC

PC Speech was recorded using a personal computer or tablet.

PhoneLine

PHONE_LINE Speech was recorded over a phone line.

Vehicle

VEHICLE Speech was recorded in a vehicle.

OtherOutdoorDevice

OTHER_OUTDOOR_DEVICE Speech was recorded outdoors.

OtherIndoorDevice

OTHER_INDOOR_DEVICE Speech was recorded indoors.

Instances
Enum RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Eq RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Data RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Methods

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

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

toConstr :: RecognitionMetadataRecordingDeviceType -> Constr #

dataTypeOf :: RecognitionMetadataRecordingDeviceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Read RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Show RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Generic RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Hashable RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToJSON RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromJSON RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromHttpApiData RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToHttpApiData RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataRecordingDeviceType Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataRecordingDeviceType = D1 (MetaData "RecognitionMetadataRecordingDeviceType" "Network.Google.Speech.Types.Sum" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) ((C1 (MetaCons "RecordingDeviceTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Smartphone" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PC" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "PhoneLine" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Vehicle" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OtherOutdoorDevice" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OtherIndoorDevice" PrefixI False) (U1 :: Type -> Type))))

RecognitionMetadataMicrophoneDistance

data RecognitionMetadataMicrophoneDistance Source #

The audio type that most closely describes the audio being recognized.

Constructors

MicrophoneDistanceUnspecified

MICROPHONE_DISTANCE_UNSPECIFIED Audio type is not known.

Nearfield

NEARFIELD The audio was captured from a closely placed microphone. Eg. phone, dictaphone, or handheld microphone. Generally if there speaker is within 1 meter of the microphone.

Midfield

MIDFIELD The speaker if within 3 meters of the microphone.

Farfield

FARFIELD The speaker is more than 3 meters away from the microphone.

Instances
Enum RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Eq RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Data RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Methods

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

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

toConstr :: RecognitionMetadataMicrophoneDistance -> Constr #

dataTypeOf :: RecognitionMetadataMicrophoneDistance -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Read RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Show RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Generic RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Hashable RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToJSON RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromJSON RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromHttpApiData RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToHttpApiData RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataMicrophoneDistance Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionMetadataMicrophoneDistance = D1 (MetaData "RecognitionMetadataMicrophoneDistance" "Network.Google.Speech.Types.Sum" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) ((C1 (MetaCons "MicrophoneDistanceUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Nearfield" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Midfield" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Farfield" PrefixI False) (U1 :: Type -> Type)))

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.Speech.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Methods

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

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

Data Xgafv Source # 
Instance details

Defined in Network.Google.Speech.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.Speech.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.Speech.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.Speech.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.Speech.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

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

LongRunningRecognizeResponse

data LongRunningRecognizeResponse Source #

The only message returned to the client by the `LongRunningRecognize` method. It contains the result as zero or more sequential `SpeechRecognitionResult` messages. It is included in the `result.response` field of the `Operation` returned by the `GetOperation` call of the `google::longrunning::Operations` service.

See: longRunningRecognizeResponse smart constructor.

Instances
Eq LongRunningRecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data LongRunningRecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: LongRunningRecognizeResponse -> Constr #

dataTypeOf :: LongRunningRecognizeResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LongRunningRecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic LongRunningRecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep LongRunningRecognizeResponse :: Type -> Type #

ToJSON LongRunningRecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON LongRunningRecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep LongRunningRecognizeResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep LongRunningRecognizeResponse = D1 (MetaData "LongRunningRecognizeResponse" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" True) (C1 (MetaCons "LongRunningRecognizeResponse'" PrefixI True) (S1 (MetaSel (Just "_lrrrResults") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [SpeechRecognitionResult]))))

longRunningRecognizeResponse :: LongRunningRecognizeResponse Source #

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

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

lrrrResults :: Lens' LongRunningRecognizeResponse [SpeechRecognitionResult] Source #

Output only. Sequential list of transcription results corresponding to sequential portions of audio.

RecognitionConfig

data RecognitionConfig Source #

Provides information to the recognizer that specifies how to process the request.

See: recognitionConfig smart constructor.

Instances
Eq RecognitionConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data RecognitionConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: RecognitionConfig -> Constr #

dataTypeOf :: RecognitionConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RecognitionConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic RecognitionConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep RecognitionConfig :: Type -> Type #

ToJSON RecognitionConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON RecognitionConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognitionConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep RecognitionConfig = D1 (MetaData "RecognitionConfig" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "RecognitionConfig'" PrefixI True) ((((S1 (MetaSel (Just "_rcEnableWordTimeOffSets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_rcSpeechContexts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SpeechContext]))) :*: (S1 (MetaSel (Just "_rcLanguageCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rcDiarizationConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SpeakerDiarizationConfig)))) :*: ((S1 (MetaSel (Just "_rcSampleRateHertz") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_rcEnableAutomaticPunctuation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "_rcMaxAlternatives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: (S1 (MetaSel (Just "_rcAudioChannelCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_rcEnableSeparateRecognitionPerChannel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) :*: (((S1 (MetaSel (Just "_rcModel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rcEnableSpeakerDiarization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "_rcMetadata") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecognitionMetadata)) :*: S1 (MetaSel (Just "_rcUseEnhanced") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) :*: ((S1 (MetaSel (Just "_rcProfanityFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_rcDiarizationSpeakerCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) :*: (S1 (MetaSel (Just "_rcEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecognitionConfigEncoding)) :*: (S1 (MetaSel (Just "_rcAlternativeLanguageCodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_rcEnableWordConfidence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

rcEnableWordTimeOffSets :: Lens' RecognitionConfig (Maybe Bool) Source #

  • Optional* If `true`, the top result includes a list of words and the start and end time offsets (timestamps) for those words. If `false`, no word-level time offset information is returned. The default is `false`.

rcSpeechContexts :: Lens' RecognitionConfig [SpeechContext] Source #

  • Optional* array of SpeechContext. A means to provide context to assist the speech recognition. For more information, see Phrase Hints.

rcLanguageCode :: Lens' RecognitionConfig (Maybe Text) Source #

  • Required* The language of the supplied audio as a BCP-47 language tag. Example: "en-US". See Language Support for a list of the currently supported language codes.

rcDiarizationConfig :: Lens' RecognitionConfig (Maybe SpeakerDiarizationConfig) Source #

  • Optional* Config to enable speaker diarization and set additional parameters to make diarization better suited for your application. Note: When this is enabled, we send all the words from the beginning of the audio for the top alternative in every consecutive STREAMING responses. This is done in order to improve our speaker tags as our models learn to identify the speakers in the conversation over time. For non-streaming requests, the diarization results will be provided only in the top alternative of the FINAL SpeechRecognitionResult.

rcSampleRateHertz :: Lens' RecognitionConfig (Maybe Int32) Source #

Sample rate in Hertz of the audio data sent in all `RecognitionAudio` messages. Valid values are: 8000-48000. 16000 is optimal. For best results, set the sampling rate of the audio source to 16000 Hz. If that's not possible, use the native sample rate of the audio source (instead of re-sampling). This field is optional for `FLAC` and `WAV` audio files and required for all other audio formats. For details, see AudioEncoding.

rcEnableAutomaticPunctuation :: Lens' RecognitionConfig (Maybe Bool) Source #

  • Optional* If 'true', adds punctuation to recognition result hypotheses. This feature is only available in select languages. Setting this for requests in other languages has no effect at all. The default 'false' value does not add punctuation to result hypotheses. Note: This is currently offered as an experimental service, complimentary to all users. In the future this may be exclusively available as a premium feature.

rcMaxAlternatives :: Lens' RecognitionConfig (Maybe Int32) Source #

  • Optional* Maximum number of recognition hypotheses to be returned. Specifically, the maximum number of `SpeechRecognitionAlternative` messages within each `SpeechRecognitionResult`. The server may return fewer than `max_alternatives`. Valid values are `0`-`30`. A value of `0` or `1` will return a maximum of one. If omitted, will return a maximum of one.

rcAudioChannelCount :: Lens' RecognitionConfig (Maybe Int32) Source #

  • Optional* The number of channels in the input audio data. ONLY set this for MULTI-CHANNEL recognition. Valid values for LINEAR16 and FLAC are `1`-`8`. Valid values for OGG_OPUS are '1'-'254'. Valid value for MULAW, AMR, AMR_WB and SPEEX_WITH_HEADER_BYTE is only `1`. If `0` or omitted, defaults to one channel (mono). Note: We only recognize the first channel by default. To perform independent recognition on each channel set `enable_separate_recognition_per_channel` to 'true'.

rcEnableSeparateRecognitionPerChannel :: Lens' RecognitionConfig (Maybe Bool) Source #

This needs to be set to ‘true’ explicitly and `audio_channel_count` > 1 to get each channel recognized separately. The recognition result will contain a `channel_tag` field to state which channel that result belongs to. If this is not true, we will only recognize the first channel. The request is billed cumulatively for all channels recognized: `audio_channel_count` multiplied by the length of the audio.

rcModel :: Lens' RecognitionConfig (Maybe Text) Source #

  • Optional* Which model to select for the given request. Select the model best suited to your domain to get best results. If a model is not explicitly specified, then we auto-select a model based on the parameters in the RecognitionConfig. > ---------------------- ------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------ > Model Description > command_and_search Best for short queries such as voice commands or voice search. > phone_call Best for audio that originated from a phone call (typically recorded at an 8khz sampling rate). > video Best for audio that originated from from video or includes multiple speakers. Ideally the audio is recorded at a 16khz or greater sampling rate. This is a premium model that costs more than the standard rate. > 'default' Best for audio that is not one of the specific audio models. For example, long-form audio. Ideally the audio is high-fidelity, recorded at a 16khz or greater sampling rate. > ---------------------- ------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------

rcEnableSpeakerDiarization :: Lens' RecognitionConfig (Maybe Bool) Source #

  • Optional* If 'true', enables speaker detection for each recognized word in the top alternative of the recognition result using a speaker_tag provided in the WordInfo. Note: Use diarization_config instead. This field will be DEPRECATED soon.

rcMetadata :: Lens' RecognitionConfig (Maybe RecognitionMetadata) Source #

  • Optional* Metadata regarding this request.

rcUseEnhanced :: Lens' RecognitionConfig (Maybe Bool) Source #

  • Optional* Set to true to use an enhanced model for speech recognition. If `use_enhanced` is set to true and the `model` field is not set, then an appropriate enhanced model is chosen if: 1. project is eligible for requesting enhanced models 2. an enhanced model exists for the audio If `use_enhanced` is true and an enhanced version of the specified model does not exist, then the speech is recognized using the standard version of the specified model. Enhanced speech models require that you opt-in to data logging using instructions in the documentation. If you set `use_enhanced` to true and you have not enabled audio logging, then you will receive an error.

rcProfanityFilter :: Lens' RecognitionConfig (Maybe Bool) Source #

  • Optional* If set to `true`, the server will attempt to filter out profanities, replacing all but the initial character in each filtered word with asterisks, e.g. "f***". If set to `false` or omitted, profanities won't be filtered out.

rcDiarizationSpeakerCount :: Lens' RecognitionConfig (Maybe Int32) Source #

  • Optional* If set, specifies the estimated number of speakers in the conversation. If not set, defaults to '2'. Ignored unless enable_speaker_diarization is set to true." Note: Use diarization_config instead. This field will be DEPRECATED soon.

rcEncoding :: Lens' RecognitionConfig (Maybe RecognitionConfigEncoding) Source #

Encoding of audio data sent in all `RecognitionAudio` messages. This field is optional for `FLAC` and `WAV` audio files and required for all other audio formats. For details, see AudioEncoding.

rcAlternativeLanguageCodes :: Lens' RecognitionConfig [Text] Source #

  • Optional* A list of up to 3 additional BCP-47 language tags, listing possible alternative languages of the supplied audio. See Language Support for a list of the currently supported language codes. If alternative languages are listed, recognition result will contain recognition in the most likely language detected including the main language_code. The recognition result will include the language tag of the language detected in the audio. Note: This feature is only supported for Voice Command and Voice Search use cases and performance may vary for other use cases (e.g., phone call transcription).

rcEnableWordConfidence :: Lens' RecognitionConfig (Maybe Bool) Source #

  • Optional* If `true`, the top result includes a list of words and the confidence for those words. If `false`, no word-level confidence information is returned. The default is `false`.

LongRunningRecognizeRequest

data LongRunningRecognizeRequest Source #

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

See: longRunningRecognizeRequest smart constructor.

Instances
Eq LongRunningRecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data LongRunningRecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: LongRunningRecognizeRequest -> Constr #

dataTypeOf :: LongRunningRecognizeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LongRunningRecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic LongRunningRecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep LongRunningRecognizeRequest :: Type -> Type #

ToJSON LongRunningRecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON LongRunningRecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep LongRunningRecognizeRequest Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep LongRunningRecognizeRequest = D1 (MetaData "LongRunningRecognizeRequest" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "LongRunningRecognizeRequest'" PrefixI True) (S1 (MetaSel (Just "_lrrrConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecognitionConfig)) :*: S1 (MetaSel (Just "_lrrrAudio") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecognitionAudio))))

longRunningRecognizeRequest :: LongRunningRecognizeRequest Source #

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

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

lrrrConfig :: Lens' LongRunningRecognizeRequest (Maybe RecognitionConfig) Source #

  • Required* Provides information to the recognizer that specifies how to process the request.

lrrrAudio :: Lens' LongRunningRecognizeRequest (Maybe RecognitionAudio) Source #

  • Required* The audio data to be recognized.

OperationMetadata

data OperationMetadata Source #

Service-specific metadata associated with the operation. It typically contains progress information and common metadata such as create time. Some services might not provide such metadata. Any method that returns a long-running operation should document the metadata type, if any.

See: operationMetadata smart constructor.

Instances
Eq OperationMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data OperationMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: OperationMetadata -> Constr #

dataTypeOf :: OperationMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OperationMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic OperationMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep OperationMetadata :: Type -> Type #

ToJSON OperationMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON OperationMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep OperationMetadata Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep OperationMetadata = D1 (MetaData "OperationMetadata" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" True) (C1 (MetaCons "OperationMetadata'" PrefixI True) (S1 (MetaSel (Just "_omAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

operationMetadata Source #

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

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

omAddtional :: Lens' OperationMetadata (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

RecognitionConfigEncoding

data RecognitionConfigEncoding Source #

Encoding of audio data sent in all `RecognitionAudio` messages. This field is optional for `FLAC` and `WAV` audio files and required for all other audio formats. For details, see AudioEncoding.

Constructors

EncodingUnspecified

ENCODING_UNSPECIFIED Not specified.

LINEAR16

LINEAR16 Uncompressed 16-bit signed little-endian samples (Linear PCM).

Flac

FLAC `FLAC` (Free Lossless Audio Codec) is the recommended encoding because it is lossless--therefore recognition is not compromised--and requires only about half the bandwidth of `LINEAR16`. `FLAC` stream encoding supports 16-bit and 24-bit samples, however, not all fields in `STREAMINFO` are supported.

Mulaw

MULAW 8-bit samples that compand 14-bit audio samples using G.711 PCMU/mu-law.

Amr

AMR Adaptive Multi-Rate Narrowband codec. `sample_rate_hertz` must be 8000.

AmrWb

AMR_WB Adaptive Multi-Rate Wideband codec. `sample_rate_hertz` must be 16000.

OggOpus

OGG_OPUS Opus encoded audio frames in Ogg container ([OggOpus](https://wiki.xiph.org/OggOpus)). `sample_rate_hertz` must be one of 8000, 12000, 16000, 24000, or 48000.

SpeexWithHeaderByte

SPEEX_WITH_HEADER_BYTE Although the use of lossy encodings is not recommended, if a very low bitrate encoding is required, `OGG_OPUS` is highly preferred over Speex encoding. The Speex encoding supported by Cloud Speech API has a header byte in each block, as in MIME type `audio/x-speex-with-header-byte`. It is a variant of the RTP Speex encoding defined in RFC 5574. The stream is a sequence of blocks, one block per RTP packet. Each block starts with a byte containing the length of the block, in bytes, followed by one or more frames of Speex data, padded to an integral number of bytes (octets) as specified in RFC 5574. In other words, each RTP header is replaced with a single byte containing the block length. Only Speex wideband is supported. `sample_rate_hertz` must be 16000.

Instances
Enum RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Eq RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Data RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Methods

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

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

toConstr :: RecognitionConfigEncoding -> Constr #

dataTypeOf :: RecognitionConfigEncoding -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Read RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Show RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Generic RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

Associated Types

type Rep RecognitionConfigEncoding :: Type -> Type #

Hashable RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToJSON RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromJSON RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

FromHttpApiData RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

ToHttpApiData RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionConfigEncoding Source # 
Instance details

Defined in Network.Google.Speech.Types.Sum

type Rep RecognitionConfigEncoding = D1 (MetaData "RecognitionConfigEncoding" "Network.Google.Speech.Types.Sum" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (((C1 (MetaCons "EncodingUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LINEAR16" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Flac" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mulaw" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Amr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AmrWb" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OggOpus" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SpeexWithHeaderByte" PrefixI False) (U1 :: Type -> Type))))

OperationResponse

data OperationResponse Source #

The normal response of the operation in case of success. If the original method returns no data on success, such as `Delete`, the response is `google.protobuf.Empty`. If the original method is standard `Get`/`Create`/`Update`, the response should be the resource. For other methods, the response should have the type `XxxResponse`, where `Xxx` is the original method name. For example, if the original method name is `TakeSnapshot()`, the inferred response type is `TakeSnapshotResponse`.

See: operationResponse smart constructor.

Instances
Eq OperationResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data OperationResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: OperationResponse -> Constr #

dataTypeOf :: OperationResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OperationResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic OperationResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep OperationResponse :: Type -> Type #

ToJSON OperationResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON OperationResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep OperationResponse Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep OperationResponse = D1 (MetaData "OperationResponse" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" True) (C1 (MetaCons "OperationResponse'" PrefixI True) (S1 (MetaSel (Just "_orAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

operationResponse Source #

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

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

orAddtional :: Lens' OperationResponse (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

SpeakerDiarizationConfig

data SpeakerDiarizationConfig Source #

Instances
Eq SpeakerDiarizationConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Data SpeakerDiarizationConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Methods

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

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

toConstr :: SpeakerDiarizationConfig -> Constr #

dataTypeOf :: SpeakerDiarizationConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpeakerDiarizationConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Generic SpeakerDiarizationConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

Associated Types

type Rep SpeakerDiarizationConfig :: Type -> Type #

ToJSON SpeakerDiarizationConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

FromJSON SpeakerDiarizationConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeakerDiarizationConfig Source # 
Instance details

Defined in Network.Google.Speech.Types.Product

type Rep SpeakerDiarizationConfig = D1 (MetaData "SpeakerDiarizationConfig" "Network.Google.Speech.Types.Product" "gogol-speech-0.4.0-DjEaGflTHLS8uenGffcunS" False) (C1 (MetaCons "SpeakerDiarizationConfig'" PrefixI True) (S1 (MetaSel (Just "_sdcMinSpeakerCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: (S1 (MetaSel (Just "_sdcMaxSpeakerCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_sdcEnableSpeakerDiarization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

speakerDiarizationConfig :: SpeakerDiarizationConfig Source #

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

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

sdcMinSpeakerCount :: Lens' SpeakerDiarizationConfig (Maybe Int32) Source #

  • Optional* Only used if diarization_speaker_count is not set. Minimum number of speakers in the conversation. This range gives you more flexibility by allowing the system to automatically determine the correct number of speakers. If not set, the default value is 2.

sdcMaxSpeakerCount :: Lens' SpeakerDiarizationConfig (Maybe Int32) Source #

  • Optional* Only used if diarization_speaker_count is not set. Maximum number of speakers in the conversation. This range gives you more flexibility by allowing the system to automatically determine the correct number of speakers. If not set, the default value is 6.

sdcEnableSpeakerDiarization :: Lens' SpeakerDiarizationConfig (Maybe Bool) Source #

  • Optional* If 'true', enables speaker detection for each recognized word in the top alternative of the recognition result using a speaker_tag provided in the WordInfo.