gogol-language-0.3.0: Google Cloud Natural Language 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.Language

Contents

Description

Google Cloud Natural Language API provides natural language understanding technologies to developers. Examples include sentiment analysis, entity recognition, and text annotations.

See: Google Cloud Natural Language API Reference

Synopsis

Service Configuration

languageService :: ServiceConfig Source #

Default request referring to version v1 of the Google Cloud Natural Language 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

type LanguageAPI = DocumentsAnalyzeSyntaxResource :<|> (DocumentsAnnotateTextResource :<|> (DocumentsAnalyzeSentimentResource :<|> DocumentsAnalyzeEntitiesResource)) Source #

Represents the entirety of the methods and resources available for the Google Cloud Natural Language API service.

Resources

language.documents.analyzeEntities

language.documents.analyzeSentiment

language.documents.analyzeSyntax

language.documents.annotateText

Types

AnalyzeSyntaxRequest

data AnalyzeSyntaxRequest Source #

The syntax analysis request message.

See: analyzeSyntaxRequest smart constructor.

Instances

Eq AnalyzeSyntaxRequest Source # 
Data AnalyzeSyntaxRequest Source # 

Methods

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

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

toConstr :: AnalyzeSyntaxRequest -> Constr #

dataTypeOf :: AnalyzeSyntaxRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeSyntaxRequest Source # 
Generic AnalyzeSyntaxRequest Source # 
ToJSON AnalyzeSyntaxRequest Source # 
FromJSON AnalyzeSyntaxRequest Source # 
type Rep AnalyzeSyntaxRequest Source # 
type Rep AnalyzeSyntaxRequest = D1 (MetaData "AnalyzeSyntaxRequest" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnalyzeSyntaxRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_asrEncodingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnalyzeSyntaxRequestEncodingType))) (S1 (MetaSel (Just Symbol "_asrDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Document)))))

analyzeSyntaxRequest :: AnalyzeSyntaxRequest Source #

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

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

asrEncodingType :: Lens' AnalyzeSyntaxRequest (Maybe AnalyzeSyntaxRequestEncodingType) Source #

The encoding type used by the API to calculate offsets.

DependencyEdge

data DependencyEdge Source #

Represents dependency parse tree information for a token. (For more information on dependency labels, see http://www.aclweb.org/anthology/P13-2017

See: dependencyEdge smart constructor.

Instances

Eq DependencyEdge Source # 
Data DependencyEdge Source # 

Methods

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

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

toConstr :: DependencyEdge -> Constr #

dataTypeOf :: DependencyEdge -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DependencyEdge Source # 
Generic DependencyEdge Source # 

Associated Types

type Rep DependencyEdge :: * -> * #

ToJSON DependencyEdge Source # 
FromJSON DependencyEdge Source # 
type Rep DependencyEdge Source # 
type Rep DependencyEdge = D1 (MetaData "DependencyEdge" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "DependencyEdge'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_deHeadTokenIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_deLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DependencyEdgeLabel)))))

dependencyEdge :: DependencyEdge Source #

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

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

deHeadTokenIndex :: Lens' DependencyEdge (Maybe Int32) Source #

Represents the head of this token in the dependency tree. This is the index of the token which has an arc going to this token. The index is the position of the token in the array of tokens returned by the API method. If this token is a root token, then the `head_token_index` is its own index.

deLabel :: Lens' DependencyEdge (Maybe DependencyEdgeLabel) Source #

The parse label for the token.

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` which 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 purpose. - 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 # 

Methods

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

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

Data Status Source # 

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 # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
FromJSON Status Source # 
type Rep Status Source # 
type Rep Status = D1 (MetaData "Status" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "Status'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StatusDetailsItem]))) ((:*:) (S1 (MetaSel (Just Symbol "_sCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_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 will be 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.

PartOfSpeechProper

data PartOfSpeechProper Source #

The grammatical properness.

Constructors

ProperUnknown

PROPER_UNKNOWN Proper is not applicable in the analyzed language or is not predicted.

Proper

PROPER Proper

NotProper

NOT_PROPER Not proper

Instances

Enum PartOfSpeechProper Source # 
Eq PartOfSpeechProper Source # 
Data PartOfSpeechProper Source # 

Methods

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

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

toConstr :: PartOfSpeechProper -> Constr #

dataTypeOf :: PartOfSpeechProper -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechProper Source # 
Read PartOfSpeechProper Source # 
Show PartOfSpeechProper Source # 
Generic PartOfSpeechProper Source # 
Hashable PartOfSpeechProper Source # 
ToJSON PartOfSpeechProper Source # 
FromJSON PartOfSpeechProper Source # 
FromHttpApiData PartOfSpeechProper Source # 
ToHttpApiData PartOfSpeechProper Source # 
type Rep PartOfSpeechProper Source # 
type Rep PartOfSpeechProper = D1 (MetaData "PartOfSpeechProper" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) (C1 (MetaCons "ProperUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "Proper" PrefixI False) U1) (C1 (MetaCons "NotProper" PrefixI False) U1)))

PartOfSpeechTag

data PartOfSpeechTag Source #

The part of speech tag.

Constructors

Unknown

UNKNOWN Unknown

Adj

ADJ Adjective

Adp

ADP Adposition (preposition and postposition)

Adv

ADV Adverb

Conj

CONJ Conjunction

Det

DET Determiner

Noun

NOUN Noun (common and proper)

Num

NUM Cardinal number

Pron

PRON Pronoun

Prt

PRT Particle or other function word

Punct

PUNCT Punctuation

Verb

VERB Verb (all tenses and modes)

X

X Other: foreign words, typos, abbreviations

Affix

AFFIX Affix

Instances

Enum PartOfSpeechTag Source # 
Eq PartOfSpeechTag Source # 
Data PartOfSpeechTag Source # 

Methods

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

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

toConstr :: PartOfSpeechTag -> Constr #

dataTypeOf :: PartOfSpeechTag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechTag Source # 
Read PartOfSpeechTag Source # 
Show PartOfSpeechTag Source # 
Generic PartOfSpeechTag Source # 
Hashable PartOfSpeechTag Source # 
ToJSON PartOfSpeechTag Source # 
FromJSON PartOfSpeechTag Source # 
FromHttpApiData PartOfSpeechTag Source # 
ToHttpApiData PartOfSpeechTag Source # 
type Rep PartOfSpeechTag Source # 
type Rep PartOfSpeechTag = D1 (MetaData "PartOfSpeechTag" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Unknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "Adj" PrefixI False) U1) (C1 (MetaCons "Adp" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Adv" PrefixI False) U1) (C1 (MetaCons "Conj" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Det" PrefixI False) U1) (C1 (MetaCons "Noun" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Num" PrefixI False) U1) ((:+:) (C1 (MetaCons "Pron" PrefixI False) U1) (C1 (MetaCons "Prt" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Punct" PrefixI False) U1) (C1 (MetaCons "Verb" PrefixI False) U1)) ((:+:) (C1 (MetaCons "X" PrefixI False) U1) (C1 (MetaCons "Affix" PrefixI False) U1)))))

Sentiment

data Sentiment Source #

Represents the feeling associated with the entire text or entities in the text.

See: sentiment smart constructor.

Instances

Eq Sentiment Source # 
Data Sentiment Source # 

Methods

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

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

toConstr :: Sentiment -> Constr #

dataTypeOf :: Sentiment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Sentiment Source # 
Generic Sentiment Source # 

Associated Types

type Rep Sentiment :: * -> * #

ToJSON Sentiment Source # 
FromJSON Sentiment Source # 
type Rep Sentiment Source # 
type Rep Sentiment = D1 (MetaData "Sentiment" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "Sentiment'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_sMagnitude") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))

sentiment :: Sentiment Source #

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

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

sScore :: Lens' Sentiment (Maybe Double) Source #

Sentiment score between -1.0 (negative sentiment) and 1.0 (positive sentiment).

sMagnitude :: Lens' Sentiment (Maybe Double) Source #

A non-negative number in the [0, +inf) range, which represents the absolute magnitude of sentiment regardless of score (positive or negative).

DocumentType

data DocumentType Source #

Required. If the type is not set or is `TYPE_UNSPECIFIED`, returns an `INVALID_ARGUMENT` error.

Constructors

TypeUnspecified

TYPE_UNSPECIFIED The content type is not specified.

PlainText

PLAIN_TEXT Plain text

HTML

HTML HTML

Instances

Enum DocumentType Source # 
Eq DocumentType Source # 
Data DocumentType Source # 

Methods

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

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

toConstr :: DocumentType -> Constr #

dataTypeOf :: DocumentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DocumentType Source # 
Read DocumentType Source # 
Show DocumentType Source # 
Generic DocumentType Source # 

Associated Types

type Rep DocumentType :: * -> * #

Hashable DocumentType Source # 
ToJSON DocumentType Source # 
FromJSON DocumentType Source # 
FromHttpApiData DocumentType Source # 
ToHttpApiData DocumentType Source # 
type Rep DocumentType Source # 
type Rep DocumentType = D1 (MetaData "DocumentType" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) (C1 (MetaCons "TypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "PlainText" PrefixI False) U1) (C1 (MetaCons "HTML" PrefixI False) U1)))

AnalyzeSyntaxRequestEncodingType

data AnalyzeSyntaxRequestEncodingType Source #

The encoding type used by the API to calculate offsets.

Constructors

None

NONE If `EncodingType` is not specified, encoding-dependent information (such as `begin_offset`) will be set at `-1`.

UTF8

UTF8 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-8 encoding of the input. C++ and Go are examples of languages that use this encoding natively.

UTF16

UTF16 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-16 encoding of the input. Java and Javascript are examples of languages that use this encoding natively.

UTF32

UTF32 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-32 encoding of the input. Python is an example of a language that uses this encoding natively.

Instances

Enum AnalyzeSyntaxRequestEncodingType Source # 
Eq AnalyzeSyntaxRequestEncodingType Source # 
Data AnalyzeSyntaxRequestEncodingType Source # 

Methods

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

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

toConstr :: AnalyzeSyntaxRequestEncodingType -> Constr #

dataTypeOf :: AnalyzeSyntaxRequestEncodingType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnalyzeSyntaxRequestEncodingType Source # 
Read AnalyzeSyntaxRequestEncodingType Source # 
Show AnalyzeSyntaxRequestEncodingType Source # 
Generic AnalyzeSyntaxRequestEncodingType Source # 
Hashable AnalyzeSyntaxRequestEncodingType Source # 
ToJSON AnalyzeSyntaxRequestEncodingType Source # 
FromJSON AnalyzeSyntaxRequestEncodingType Source # 
FromHttpApiData AnalyzeSyntaxRequestEncodingType Source # 
ToHttpApiData AnalyzeSyntaxRequestEncodingType Source # 
type Rep AnalyzeSyntaxRequestEncodingType Source # 
type Rep AnalyzeSyntaxRequestEncodingType = D1 (MetaData "AnalyzeSyntaxRequestEncodingType" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "None" PrefixI False) U1) (C1 (MetaCons "UTF8" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UTF16" PrefixI False) U1) (C1 (MetaCons "UTF32" PrefixI False) U1)))

DependencyEdgeLabel

data DependencyEdgeLabel Source #

The parse label for the token.

Constructors

DELUnknown

UNKNOWN Unknown

DELAbbrev

ABBREV Abbreviation modifier

DELAcomp

ACOMP Adjectival complement

DELAdvcl

ADVCL Adverbial clause modifier

DELAdvmod

ADVMOD Adverbial modifier

DELAmod

AMOD Adjectival modifier of an NP

DELAppos

APPOS Appositional modifier of an NP

DELAttr

ATTR Attribute dependent of a copular verb

DELAux

AUX Auxiliary (non-main) verb

DELAuxpass

AUXPASS Passive auxiliary

DELCC

CC Coordinating conjunction

DELCcomp

CCOMP Clausal complement of a verb or adjective

DELConj

CONJ Conjunct

DELCsubj

CSUBJ Clausal subject

DELCsubjpass

CSUBJPASS Clausal passive subject

DELDep

DEP Dependency (unable to determine)

DELDet

DET Determiner

DELDiscourse

DISCOURSE Discourse

DELDobj

DOBJ Direct object

DELExpl

EXPL Expletive

DELGoeswith

GOESWITH Goes with (part of a word in a text not well edited)

DELIobj

IOBJ Indirect object

DELMark

MARK Marker (word introducing a subordinate clause)

DELMwe

MWE Multi-word expression

DELMwv

MWV Multi-word verbal expression

DELNeg

NEG Negation modifier

DELNN

NN Noun compound modifier

DELNpadvmod

NPADVMOD Noun phrase used as an adverbial modifier

DELNsubj

NSUBJ Nominal subject

DELNsubjpass

NSUBJPASS Passive nominal subject

DELNum

NUM Numeric modifier of a noun

DELNumber

NUMBER Element of compound number

DELP

P Punctuation mark

DELParataxis

PARATAXIS Parataxis relation

DELPartmod

PARTMOD Participial modifier

DELPcomp

PCOMP The complement of a preposition is a clause

DELPobj

POBJ Object of a preposition

DELPoss

POSS Possession modifier

DELPostneg

POSTNEG Postverbal negative particle

DELPrecomp

PRECOMP Predicate complement

DELPreconj

PRECONJ Preconjunt

DELPredet

PREDET Predeterminer

DELPref

PREF Prefix

DELPrep

PREP Prepositional modifier

DELPronl

PRONL The relationship between a verb and verbal morpheme

DELPrt

PRT Particle

DELPS

PS Associative or possessive marker

DELQuantmod

QUANTMOD Quantifier phrase modifier

DELRcmod

RCMOD Relative clause modifier

DELRcmodrel

RCMODREL Complementizer in relative clause

DELRdrop

RDROP Ellipsis without a preceding predicate

DELRef

REF Referent

DELRemnant

REMNANT Remnant

DELReparandum

REPARANDUM Reparandum

DELRoot

ROOT Root

DELSnum

SNUM Suffix specifying a unit of number

DELSuff

SUFF Suffix

DELTmod

TMOD Temporal modifier

DELTopic

TOPIC Topic marker

DELVMod

VMOD Clause headed by an infinite form of the verb that modifies a noun

DELVocative

VOCATIVE Vocative

DELXcomp

XCOMP Open clausal complement

DELSuffix

SUFFIX Name suffix

DELTitle

TITLE Name title

DELAdvphmod

ADVPHMOD Adverbial phrase modifier

DELAuxcaus

AUXCAUS Causative auxiliary

DELAuxvv

AUXVV Helper auxiliary

DELDtmod

DTMOD Rentaishi (Prenominal modifier)

DELForeign

FOREIGN Foreign words

DELKW

KW Keyword

DELList

LIST List for chains of comparable items

DELNomc

NOMC Nominalized clause

DELNomcsubj

NOMCSUBJ Nominalized clausal subject

DELNomcsubjpass

NOMCSUBJPASS Nominalized clausal passive

DELNumc

NUMC Compound of numeric modifier

DELCop

COP Copula

DELDislocated

DISLOCATED Dislocated relation (for fronted/topicalized elements)

Instances

Enum DependencyEdgeLabel Source # 
Eq DependencyEdgeLabel Source # 
Data DependencyEdgeLabel Source # 

Methods

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

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

toConstr :: DependencyEdgeLabel -> Constr #

dataTypeOf :: DependencyEdgeLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DependencyEdgeLabel Source # 
Read DependencyEdgeLabel Source # 
Show DependencyEdgeLabel Source # 
Generic DependencyEdgeLabel Source # 
Hashable DependencyEdgeLabel Source # 
ToJSON DependencyEdgeLabel Source # 
FromJSON DependencyEdgeLabel Source # 
FromHttpApiData DependencyEdgeLabel Source # 
ToHttpApiData DependencyEdgeLabel Source # 
type Rep DependencyEdgeLabel Source # 
type Rep DependencyEdgeLabel = D1 (MetaData "DependencyEdgeLabel" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELUnknown" PrefixI False) U1) (C1 (MetaCons "DELAbbrev" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELAcomp" PrefixI False) U1) (C1 (MetaCons "DELAdvcl" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "DELAdvmod" PrefixI False) U1) (C1 (MetaCons "DELAmod" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELAppos" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELAttr" PrefixI False) U1) (C1 (MetaCons "DELAux" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELAuxpass" PrefixI False) U1) (C1 (MetaCons "DELCC" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELCcomp" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELConj" PrefixI False) U1) (C1 (MetaCons "DELCsubj" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "DELCsubjpass" PrefixI False) U1) (C1 (MetaCons "DELDep" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELDet" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELDiscourse" PrefixI False) U1) (C1 (MetaCons "DELDobj" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELExpl" PrefixI False) U1) (C1 (MetaCons "DELGoeswith" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELIobj" PrefixI False) U1) (C1 (MetaCons "DELMark" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "DELMwe" PrefixI False) U1) (C1 (MetaCons "DELMwv" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELNeg" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELNN" PrefixI False) U1) (C1 (MetaCons "DELNpadvmod" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELNsubj" PrefixI False) U1) (C1 (MetaCons "DELNsubjpass" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELNum" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELNumber" PrefixI False) U1) (C1 (MetaCons "DELP" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "DELParataxis" PrefixI False) U1) (C1 (MetaCons "DELPartmod" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELPcomp" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELPobj" PrefixI False) U1) (C1 (MetaCons "DELPoss" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELPostneg" PrefixI False) U1) (C1 (MetaCons "DELPrecomp" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELPreconj" PrefixI False) U1) (C1 (MetaCons "DELPredet" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "DELPref" PrefixI False) U1) (C1 (MetaCons "DELPrep" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELPronl" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELPrt" PrefixI False) U1) (C1 (MetaCons "DELPS" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELQuantmod" PrefixI False) U1) (C1 (MetaCons "DELRcmod" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELRcmodrel" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELRdrop" PrefixI False) U1) (C1 (MetaCons "DELRef" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "DELRemnant" PrefixI False) U1) (C1 (MetaCons "DELReparandum" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELRoot" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELSnum" PrefixI False) U1) (C1 (MetaCons "DELSuff" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELTmod" PrefixI False) U1) (C1 (MetaCons "DELTopic" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELVMod" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELVocative" PrefixI False) U1) (C1 (MetaCons "DELXcomp" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "DELSuffix" PrefixI False) U1) (C1 (MetaCons "DELTitle" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELAdvphmod" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELAuxcaus" PrefixI False) U1) (C1 (MetaCons "DELAuxvv" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DELDtmod" PrefixI False) U1) (C1 (MetaCons "DELForeign" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELKW" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELList" PrefixI False) U1) (C1 (MetaCons "DELNomc" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "DELNomcsubj" PrefixI False) U1) (C1 (MetaCons "DELNomcsubjpass" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DELNumc" PrefixI False) U1) ((:+:) (C1 (MetaCons "DELCop" PrefixI False) U1) (C1 (MetaCons "DELDislocated" PrefixI False) U1))))))))

PartOfSpeechVoice

data PartOfSpeechVoice Source #

The grammatical voice.

Constructors

VoiceUnknown

VOICE_UNKNOWN Voice is not applicable in the analyzed language or is not predicted.

Active

ACTIVE Active

Causative

CAUSATIVE Causative

Passive

PASSIVE Passive

Instances

Enum PartOfSpeechVoice Source # 
Eq PartOfSpeechVoice Source # 
Data PartOfSpeechVoice Source # 

Methods

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

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

toConstr :: PartOfSpeechVoice -> Constr #

dataTypeOf :: PartOfSpeechVoice -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechVoice Source # 
Read PartOfSpeechVoice Source # 
Show PartOfSpeechVoice Source # 
Generic PartOfSpeechVoice Source # 
Hashable PartOfSpeechVoice Source # 
ToJSON PartOfSpeechVoice Source # 
FromJSON PartOfSpeechVoice Source # 
FromHttpApiData PartOfSpeechVoice Source # 
ToHttpApiData PartOfSpeechVoice Source # 
type Rep PartOfSpeechVoice Source # 
type Rep PartOfSpeechVoice = D1 (MetaData "PartOfSpeechVoice" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "VoiceUnknown" PrefixI False) U1) (C1 (MetaCons "Active" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Causative" PrefixI False) U1) (C1 (MetaCons "Passive" PrefixI False) U1)))

PartOfSpeechForm

data PartOfSpeechForm Source #

The grammatical form.

Constructors

FormUnknown

FORM_UNKNOWN Form is not applicable in the analyzed language or is not predicted.

Adnomial

ADNOMIAL Adnomial

Auxiliary

AUXILIARY Auxiliary

Complementizer

COMPLEMENTIZER Complementizer

FinalEnding

FINAL_ENDING Final ending

Gerund

GERUND Gerund

Realis

REALIS Realis

Irrealis

IRREALIS Irrealis

Short

SHORT Short form

Long

LONG Long form

Order

ORDER Order form

Specific

SPECIFIC Specific form

Instances

Enum PartOfSpeechForm Source # 
Eq PartOfSpeechForm Source # 
Data PartOfSpeechForm Source # 

Methods

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

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

toConstr :: PartOfSpeechForm -> Constr #

dataTypeOf :: PartOfSpeechForm -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechForm Source # 
Read PartOfSpeechForm Source # 
Show PartOfSpeechForm Source # 
Generic PartOfSpeechForm Source # 
Hashable PartOfSpeechForm Source # 
ToJSON PartOfSpeechForm Source # 
FromJSON PartOfSpeechForm Source # 
FromHttpApiData PartOfSpeechForm Source # 
ToHttpApiData PartOfSpeechForm Source # 
type Rep PartOfSpeechForm Source # 
type Rep PartOfSpeechForm = D1 (MetaData "PartOfSpeechForm" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FormUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "Adnomial" PrefixI False) U1) (C1 (MetaCons "Auxiliary" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Complementizer" PrefixI False) U1) ((:+:) (C1 (MetaCons "FinalEnding" PrefixI False) U1) (C1 (MetaCons "Gerund" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Realis" PrefixI False) U1) ((:+:) (C1 (MetaCons "Irrealis" PrefixI False) U1) (C1 (MetaCons "Short" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Long" PrefixI False) U1) ((:+:) (C1 (MetaCons "Order" PrefixI False) U1) (C1 (MetaCons "Specific" PrefixI False) U1)))))

PartOfSpeechPerson

data PartOfSpeechPerson Source #

The grammatical person.

Constructors

PersonUnknown

PERSON_UNKNOWN Person is not applicable in the analyzed language or is not predicted.

First

FIRST First

Second

SECOND Second

Third

THIRD Third

ReflexivePerson

REFLEXIVE_PERSON Reflexive

Instances

Enum PartOfSpeechPerson Source # 
Eq PartOfSpeechPerson Source # 
Data PartOfSpeechPerson Source # 

Methods

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

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

toConstr :: PartOfSpeechPerson -> Constr #

dataTypeOf :: PartOfSpeechPerson -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechPerson Source # 
Read PartOfSpeechPerson Source # 
Show PartOfSpeechPerson Source # 
Generic PartOfSpeechPerson Source # 
Hashable PartOfSpeechPerson Source # 
ToJSON PartOfSpeechPerson Source # 
FromJSON PartOfSpeechPerson Source # 
FromHttpApiData PartOfSpeechPerson Source # 
ToHttpApiData PartOfSpeechPerson Source # 
type Rep PartOfSpeechPerson Source # 
type Rep PartOfSpeechPerson = D1 (MetaData "PartOfSpeechPerson" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "PersonUnknown" PrefixI False) U1) (C1 (MetaCons "First" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Second" PrefixI False) U1) ((:+:) (C1 (MetaCons "Third" PrefixI False) U1) (C1 (MetaCons "ReflexivePerson" PrefixI False) U1))))

Token

data Token Source #

Represents the smallest syntactic building block of the text.

See: token smart constructor.

Instances

Eq Token Source # 

Methods

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

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

Data Token Source # 

Methods

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

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

toConstr :: Token -> Constr #

dataTypeOf :: Token -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Token Source # 

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 

Associated Types

type Rep Token :: * -> * #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

ToJSON Token Source # 
FromJSON Token Source # 
type Rep Token Source # 
type Rep Token = D1 (MetaData "Token" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "Token'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tDependencyEdge") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DependencyEdge))) (S1 (MetaSel (Just Symbol "_tText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextSpan)))) ((:*:) (S1 (MetaSel (Just Symbol "_tLemma") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tPartOfSpeech") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeech))))))

token :: Token Source #

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

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

tDependencyEdge :: Lens' Token (Maybe DependencyEdge) Source #

Dependency tree parse for this token.

tText :: Lens' Token (Maybe TextSpan) Source #

The token text.

tLemma :: Lens' Token (Maybe Text) Source #

Lemma of the token.

tPartOfSpeech :: Lens' Token (Maybe PartOfSpeech) Source #

Parts of speech tag for this token.

EntityType

data EntityType Source #

The entity type.

Constructors

ETUnknown

UNKNOWN Unknown

ETPerson

PERSON Person

ETLocation

LOCATION Location

ETOrganization

ORGANIZATION Organization

ETEvent

EVENT Event

ETWorkOfArt

WORK_OF_ART Work of art

ETConsumerGood

CONSUMER_GOOD Consumer goods

ETOther

OTHER Other types

Instances

Enum EntityType Source # 
Eq EntityType Source # 
Data EntityType Source # 

Methods

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

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

toConstr :: EntityType -> Constr #

dataTypeOf :: EntityType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EntityType Source # 
Read EntityType Source # 
Show EntityType Source # 
Generic EntityType Source # 

Associated Types

type Rep EntityType :: * -> * #

Hashable EntityType Source # 
ToJSON EntityType Source # 
FromJSON EntityType Source # 
FromHttpApiData EntityType Source # 
ToHttpApiData EntityType Source # 
type Rep EntityType Source # 
type Rep EntityType = D1 (MetaData "EntityType" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ETUnknown" PrefixI False) U1) (C1 (MetaCons "ETPerson" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ETLocation" PrefixI False) U1) (C1 (MetaCons "ETOrganization" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "ETEvent" PrefixI False) U1) (C1 (MetaCons "ETWorkOfArt" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ETConsumerGood" PrefixI False) U1) (C1 (MetaCons "ETOther" PrefixI False) U1))))

StatusDetailsItem

data StatusDetailsItem Source #

Instances

Eq StatusDetailsItem Source # 
Data StatusDetailsItem Source # 

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 # 
Generic StatusDetailsItem Source # 
ToJSON StatusDetailsItem Source # 
FromJSON StatusDetailsItem Source # 
type Rep StatusDetailsItem Source # 
type Rep StatusDetailsItem = D1 (MetaData "StatusDetailsItem" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" True) (C1 (MetaCons "StatusDetailsItem'" PrefixI True) (S1 (MetaSel (Just Symbol "_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.

AnnotateTextRequest

data AnnotateTextRequest Source #

The request message for the text annotation API, which can perform multiple analysis types (sentiment, entities, and syntax) in one call.

See: annotateTextRequest smart constructor.

Instances

Eq AnnotateTextRequest Source # 
Data AnnotateTextRequest Source # 

Methods

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

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

toConstr :: AnnotateTextRequest -> Constr #

dataTypeOf :: AnnotateTextRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnnotateTextRequest Source # 
Generic AnnotateTextRequest Source # 
ToJSON AnnotateTextRequest Source # 
FromJSON AnnotateTextRequest Source # 
type Rep AnnotateTextRequest Source # 
type Rep AnnotateTextRequest = D1 (MetaData "AnnotateTextRequest" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnnotateTextRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_atrEncodingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnnotateTextRequestEncodingType))) ((:*:) (S1 (MetaSel (Just Symbol "_atrFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Features))) (S1 (MetaSel (Just Symbol "_atrDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Document))))))

annotateTextRequest :: AnnotateTextRequest Source #

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

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

atrEncodingType :: Lens' AnnotateTextRequest (Maybe AnnotateTextRequestEncodingType) Source #

The encoding type used by the API to calculate offsets.

EntityMention

data EntityMention Source #

Represents a mention for an entity in the text. Currently, proper noun mentions are supported.

See: entityMention smart constructor.

Instances

Eq EntityMention Source # 
Data EntityMention Source # 

Methods

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

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

toConstr :: EntityMention -> Constr #

dataTypeOf :: EntityMention -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EntityMention Source # 
Generic EntityMention Source # 

Associated Types

type Rep EntityMention :: * -> * #

ToJSON EntityMention Source # 
FromJSON EntityMention Source # 
type Rep EntityMention Source # 
type Rep EntityMention = D1 (MetaData "EntityMention" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "EntityMention'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_emText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextSpan))) (S1 (MetaSel (Just Symbol "_emType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EntityMentionType)))))

entityMention :: EntityMention Source #

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

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

emType :: Lens' EntityMention (Maybe EntityMentionType) Source #

The type of the entity mention.

TextSpan

data TextSpan Source #

Represents an output piece of text.

See: textSpan smart constructor.

Instances

Eq TextSpan Source # 
Data TextSpan Source # 

Methods

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

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

toConstr :: TextSpan -> Constr #

dataTypeOf :: TextSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TextSpan Source # 
Generic TextSpan Source # 

Associated Types

type Rep TextSpan :: * -> * #

Methods

from :: TextSpan -> Rep TextSpan x #

to :: Rep TextSpan x -> TextSpan #

ToJSON TextSpan Source # 
FromJSON TextSpan Source # 
type Rep TextSpan Source # 
type Rep TextSpan = D1 (MetaData "TextSpan" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "TextSpan'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tsBeginOffSet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_tsContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

textSpan :: TextSpan Source #

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

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

tsBeginOffSet :: Lens' TextSpan (Maybe Int32) Source #

The API calculates the beginning offset of the content in the original document according to the EncodingType specified in the API request.

tsContent :: Lens' TextSpan (Maybe Text) Source #

The content of the output text.

AnnotateTextResponse

data AnnotateTextResponse Source #

The text annotations response message.

See: annotateTextResponse smart constructor.

Instances

Eq AnnotateTextResponse Source # 
Data AnnotateTextResponse Source # 

Methods

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

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

toConstr :: AnnotateTextResponse -> Constr #

dataTypeOf :: AnnotateTextResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnnotateTextResponse Source # 
Generic AnnotateTextResponse Source # 
ToJSON AnnotateTextResponse Source # 
FromJSON AnnotateTextResponse Source # 
type Rep AnnotateTextResponse Source # 
type Rep AnnotateTextResponse = D1 (MetaData "AnnotateTextResponse" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnnotateTextResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_atrEntities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Entity]))) (S1 (MetaSel (Just Symbol "_atrTokens") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Token])))) ((:*:) (S1 (MetaSel (Just Symbol "_atrDocumentSentiment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Sentiment))) ((:*:) (S1 (MetaSel (Just Symbol "_atrSentences") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Sentence]))) (S1 (MetaSel (Just Symbol "_atrLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

annotateTextResponse :: AnnotateTextResponse Source #

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

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

atrEntities :: Lens' AnnotateTextResponse [Entity] Source #

Entities, along with their semantic information, in the input document. Populated if the user enables AnnotateTextRequest.Features.extract_entities.

atrTokens :: Lens' AnnotateTextResponse [Token] Source #

Tokens, along with their syntactic information, in the input document. Populated if the user enables AnnotateTextRequest.Features.extract_syntax.

atrDocumentSentiment :: Lens' AnnotateTextResponse (Maybe Sentiment) Source #

The overall sentiment for the document. Populated if the user enables AnnotateTextRequest.Features.extract_document_sentiment.

atrSentences :: Lens' AnnotateTextResponse [Sentence] Source #

Sentences in the input document. Populated if the user enables AnnotateTextRequest.Features.extract_syntax.

atrLanguage :: Lens' AnnotateTextResponse (Maybe Text) Source #

The language of the text, which will be the same as the language specified in the request or, if not specified, the automatically-detected language. See `Document.language` field for more details.

PartOfSpeechTense

data PartOfSpeechTense Source #

The grammatical tense.

Constructors

TenseUnknown

TENSE_UNKNOWN Tense is not applicable in the analyzed language or is not predicted.

ConditionalTense

CONDITIONAL_TENSE Conditional

Future

FUTURE Future

Past

PAST Past

Present

PRESENT Present

Imperfect

IMPERFECT Imperfect

Pluperfect

PLUPERFECT Pluperfect

Instances

Enum PartOfSpeechTense Source # 
Eq PartOfSpeechTense Source # 
Data PartOfSpeechTense Source # 

Methods

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

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

toConstr :: PartOfSpeechTense -> Constr #

dataTypeOf :: PartOfSpeechTense -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechTense Source # 
Read PartOfSpeechTense Source # 
Show PartOfSpeechTense Source # 
Generic PartOfSpeechTense Source # 
Hashable PartOfSpeechTense Source # 
ToJSON PartOfSpeechTense Source # 
FromJSON PartOfSpeechTense Source # 
FromHttpApiData PartOfSpeechTense Source # 
ToHttpApiData PartOfSpeechTense Source # 
type Rep PartOfSpeechTense Source # 
type Rep PartOfSpeechTense = D1 (MetaData "PartOfSpeechTense" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "TenseUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "ConditionalTense" PrefixI False) U1) (C1 (MetaCons "Future" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Past" PrefixI False) U1) (C1 (MetaCons "Present" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Imperfect" PrefixI False) U1) (C1 (MetaCons "Pluperfect" PrefixI False) U1))))

Features

data Features Source #

All available features for sentiment, syntax, and semantic analysis. Setting each one to true will enable that specific analysis for the input.

See: features smart constructor.

Instances

Eq Features Source # 
Data Features Source # 

Methods

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

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

toConstr :: Features -> Constr #

dataTypeOf :: Features -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Features Source # 
Generic Features Source # 

Associated Types

type Rep Features :: * -> * #

Methods

from :: Features -> Rep Features x #

to :: Rep Features x -> Features #

ToJSON Features Source # 
FromJSON Features Source # 
type Rep Features Source # 
type Rep Features = D1 (MetaData "Features" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "Features'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fExtractSyntax") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_fExtractDocumentSentiment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_fExtractEntities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

features :: Features Source #

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

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

fExtractSyntax :: Lens' Features (Maybe Bool) Source #

Extract syntax information.

fExtractDocumentSentiment :: Lens' Features (Maybe Bool) Source #

Extract document-level sentiment.

Document

data Document Source #

############################################################### Represents the input to API methods.

See: document smart constructor.

Instances

Eq Document Source # 
Data Document Source # 

Methods

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

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

toConstr :: Document -> Constr #

dataTypeOf :: Document -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Document Source # 
Generic Document Source # 

Associated Types

type Rep Document :: * -> * #

Methods

from :: Document -> Rep Document x #

to :: Rep Document x -> Document #

ToJSON Document Source # 
FromJSON Document Source # 
type Rep Document Source # 
type Rep Document = D1 (MetaData "Document" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "Document'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_dGcsContentURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DocumentType))))))

document :: Document Source #

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

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

dContent :: Lens' Document (Maybe Text) Source #

The content of the input in string format.

dLanguage :: Lens' Document (Maybe Text) Source #

The language of the document (if not specified, the language is automatically detected). Both ISO and BCP-47 language codes are accepted. **Current Language Restrictions:** * Only English, Spanish, and Japanese textual content are supported. If the language (either specified by the caller or automatically detected) is not supported by the called API method, an `INVALID_ARGUMENT` error is returned.

dGcsContentURI :: Lens' Document (Maybe Text) Source #

The Google Cloud Storage URI where the file content is located. This URI must be of the form: gs://bucket_name/object_name. For more details, see https://cloud.google.com/storage/docs/reference-uris. NOTE: Cloud Storage object versioning is not supported.

dType :: Lens' Document (Maybe DocumentType) Source #

Required. If the type is not set or is `TYPE_UNSPECIFIED`, returns an `INVALID_ARGUMENT` error.

PartOfSpeechMood

data PartOfSpeechMood Source #

The grammatical mood.

Constructors

MoodUnknown

MOOD_UNKNOWN Mood is not applicable in the analyzed language or is not predicted.

ConditionalMood

CONDITIONAL_MOOD Conditional

Imperative

IMPERATIVE Imperative

Indicative

INDICATIVE Indicative

Interrogative

INTERROGATIVE Interrogative

Jussive

JUSSIVE Jussive

Subjunctive

SUBJUNCTIVE Subjunctive

Instances

Enum PartOfSpeechMood Source # 
Eq PartOfSpeechMood Source # 
Data PartOfSpeechMood Source # 

Methods

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

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

toConstr :: PartOfSpeechMood -> Constr #

dataTypeOf :: PartOfSpeechMood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechMood Source # 
Read PartOfSpeechMood Source # 
Show PartOfSpeechMood Source # 
Generic PartOfSpeechMood Source # 
Hashable PartOfSpeechMood Source # 
ToJSON PartOfSpeechMood Source # 
FromJSON PartOfSpeechMood Source # 
FromHttpApiData PartOfSpeechMood Source # 
ToHttpApiData PartOfSpeechMood Source # 
type Rep PartOfSpeechMood Source # 
type Rep PartOfSpeechMood = D1 (MetaData "PartOfSpeechMood" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "MoodUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "ConditionalMood" PrefixI False) U1) (C1 (MetaCons "Imperative" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Indicative" PrefixI False) U1) (C1 (MetaCons "Interrogative" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Jussive" PrefixI False) U1) (C1 (MetaCons "Subjunctive" PrefixI False) U1))))

PartOfSpeechCase

data PartOfSpeechCase Source #

The grammatical case.

Constructors

CaseUnknown

CASE_UNKNOWN Case is not applicable in the analyzed language or is not predicted.

Accusative

ACCUSATIVE Accusative

Adverbial

ADVERBIAL Adverbial

Complementive

COMPLEMENTIVE Complementive

Dative

DATIVE Dative

Genitive

GENITIVE Genitive

Instrumental

INSTRUMENTAL Instrumental

Locative

LOCATIVE Locative

Nominative

NOMINATIVE Nominative

Oblique

OBLIQUE Oblique

Partitive

PARTITIVE Partitive

PrePositional

PREPOSITIONAL Prepositional

ReflexiveCase

REFLEXIVE_CASE Reflexive

RelativeCase

RELATIVE_CASE Relative

Vocative

VOCATIVE Vocative

Instances

Enum PartOfSpeechCase Source # 
Eq PartOfSpeechCase Source # 
Data PartOfSpeechCase Source # 

Methods

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

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

toConstr :: PartOfSpeechCase -> Constr #

dataTypeOf :: PartOfSpeechCase -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechCase Source # 
Read PartOfSpeechCase Source # 
Show PartOfSpeechCase Source # 
Generic PartOfSpeechCase Source # 
Hashable PartOfSpeechCase Source # 
ToJSON PartOfSpeechCase Source # 
FromJSON PartOfSpeechCase Source # 
FromHttpApiData PartOfSpeechCase Source # 
ToHttpApiData PartOfSpeechCase Source # 
type Rep PartOfSpeechCase Source # 
type Rep PartOfSpeechCase = D1 (MetaData "PartOfSpeechCase" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CaseUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "Accusative" PrefixI False) U1) (C1 (MetaCons "Adverbial" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Complementive" PrefixI False) U1) (C1 (MetaCons "Dative" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Genitive" PrefixI False) U1) (C1 (MetaCons "Instrumental" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Locative" PrefixI False) U1) (C1 (MetaCons "Nominative" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Oblique" PrefixI False) U1) (C1 (MetaCons "Partitive" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PrePositional" PrefixI False) U1) (C1 (MetaCons "ReflexiveCase" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RelativeCase" PrefixI False) U1) (C1 (MetaCons "Vocative" PrefixI False) U1)))))

AnalyzeSentimentRequest

data AnalyzeSentimentRequest Source #

The sentiment analysis request message.

See: analyzeSentimentRequest smart constructor.

Instances

Eq AnalyzeSentimentRequest Source # 
Data AnalyzeSentimentRequest Source # 

Methods

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

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

toConstr :: AnalyzeSentimentRequest -> Constr #

dataTypeOf :: AnalyzeSentimentRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeSentimentRequest Source # 
Generic AnalyzeSentimentRequest Source # 
ToJSON AnalyzeSentimentRequest Source # 
FromJSON AnalyzeSentimentRequest Source # 
type Rep AnalyzeSentimentRequest Source # 
type Rep AnalyzeSentimentRequest = D1 (MetaData "AnalyzeSentimentRequest" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnalyzeSentimentRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aEncodingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnalyzeSentimentRequestEncodingType))) (S1 (MetaSel (Just Symbol "_aDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Document)))))

analyzeSentimentRequest :: AnalyzeSentimentRequest Source #

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

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

aEncodingType :: Lens' AnalyzeSentimentRequest (Maybe AnalyzeSentimentRequestEncodingType) Source #

The encoding type used by the API to calculate sentence offsets.

aDocument :: Lens' AnalyzeSentimentRequest (Maybe Document) Source #

Input document. Currently, `analyzeSentiment` only supports English text (Document.language="EN").

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances

Enum Xgafv Source # 
Eq Xgafv Source # 

Methods

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

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

Data Xgafv Source # 

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 # 

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 # 
Show Xgafv Source # 

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 

Associated Types

type Rep Xgafv :: * -> * #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
FromJSON Xgafv Source # 
FromHttpApiData Xgafv Source # 
ToHttpApiData Xgafv Source # 
type Rep Xgafv Source # 
type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) (C1 (MetaCons "X1" PrefixI False) U1) (C1 (MetaCons "X2" PrefixI False) U1))

AnalyzeEntitiesResponse

data AnalyzeEntitiesResponse Source #

The entity analysis response message.

See: analyzeEntitiesResponse smart constructor.

Instances

Eq AnalyzeEntitiesResponse Source # 
Data AnalyzeEntitiesResponse Source # 

Methods

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

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

toConstr :: AnalyzeEntitiesResponse -> Constr #

dataTypeOf :: AnalyzeEntitiesResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeEntitiesResponse Source # 
Generic AnalyzeEntitiesResponse Source # 
ToJSON AnalyzeEntitiesResponse Source # 
FromJSON AnalyzeEntitiesResponse Source # 
type Rep AnalyzeEntitiesResponse Source # 
type Rep AnalyzeEntitiesResponse = D1 (MetaData "AnalyzeEntitiesResponse" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnalyzeEntitiesResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aerEntities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Entity]))) (S1 (MetaSel (Just Symbol "_aerLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

analyzeEntitiesResponse :: AnalyzeEntitiesResponse Source #

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

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

aerEntities :: Lens' AnalyzeEntitiesResponse [Entity] Source #

The recognized entities in the input document.

aerLanguage :: Lens' AnalyzeEntitiesResponse (Maybe Text) Source #

The language of the text, which will be the same as the language specified in the request or, if not specified, the automatically-detected language. See `Document.language` field for more details.

AnnotateTextRequestEncodingType

data AnnotateTextRequestEncodingType Source #

The encoding type used by the API to calculate offsets.

Constructors

ATRETNone

NONE If `EncodingType` is not specified, encoding-dependent information (such as `begin_offset`) will be set at `-1`.

ATRETUTF8

UTF8 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-8 encoding of the input. C++ and Go are examples of languages that use this encoding natively.

ATRETUTF16

UTF16 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-16 encoding of the input. Java and Javascript are examples of languages that use this encoding natively.

ATRETUTF32

UTF32 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-32 encoding of the input. Python is an example of a language that uses this encoding natively.

Instances

Enum AnnotateTextRequestEncodingType Source # 
Eq AnnotateTextRequestEncodingType Source # 
Data AnnotateTextRequestEncodingType Source # 

Methods

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

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

toConstr :: AnnotateTextRequestEncodingType -> Constr #

dataTypeOf :: AnnotateTextRequestEncodingType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnnotateTextRequestEncodingType Source # 
Read AnnotateTextRequestEncodingType Source # 
Show AnnotateTextRequestEncodingType Source # 
Generic AnnotateTextRequestEncodingType Source # 
Hashable AnnotateTextRequestEncodingType Source # 
ToJSON AnnotateTextRequestEncodingType Source # 
FromJSON AnnotateTextRequestEncodingType Source # 
FromHttpApiData AnnotateTextRequestEncodingType Source # 
ToHttpApiData AnnotateTextRequestEncodingType Source # 
type Rep AnnotateTextRequestEncodingType Source # 
type Rep AnnotateTextRequestEncodingType = D1 (MetaData "AnnotateTextRequestEncodingType" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "ATRETNone" PrefixI False) U1) (C1 (MetaCons "ATRETUTF8" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ATRETUTF16" PrefixI False) U1) (C1 (MetaCons "ATRETUTF32" PrefixI False) U1)))

PartOfSpeechNumber

data PartOfSpeechNumber Source #

The grammatical number.

Constructors

NumberUnknown

NUMBER_UNKNOWN Number is not applicable in the analyzed language or is not predicted.

Singular

SINGULAR Singular

Plural

PLURAL Plural

Dual

DUAL Dual

Instances

Enum PartOfSpeechNumber Source # 
Eq PartOfSpeechNumber Source # 
Data PartOfSpeechNumber Source # 

Methods

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

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

toConstr :: PartOfSpeechNumber -> Constr #

dataTypeOf :: PartOfSpeechNumber -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechNumber Source # 
Read PartOfSpeechNumber Source # 
Show PartOfSpeechNumber Source # 
Generic PartOfSpeechNumber Source # 
Hashable PartOfSpeechNumber Source # 
ToJSON PartOfSpeechNumber Source # 
FromJSON PartOfSpeechNumber Source # 
FromHttpApiData PartOfSpeechNumber Source # 
ToHttpApiData PartOfSpeechNumber Source # 
type Rep PartOfSpeechNumber Source # 
type Rep PartOfSpeechNumber = D1 (MetaData "PartOfSpeechNumber" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "NumberUnknown" PrefixI False) U1) (C1 (MetaCons "Singular" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Plural" PrefixI False) U1) (C1 (MetaCons "Dual" PrefixI False) U1)))

AnalyzeSentimentResponse

data AnalyzeSentimentResponse Source #

The sentiment analysis response message.

See: analyzeSentimentResponse smart constructor.

Instances

Eq AnalyzeSentimentResponse Source # 
Data AnalyzeSentimentResponse Source # 

Methods

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

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

toConstr :: AnalyzeSentimentResponse -> Constr #

dataTypeOf :: AnalyzeSentimentResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeSentimentResponse Source # 
Generic AnalyzeSentimentResponse Source # 
ToJSON AnalyzeSentimentResponse Source # 
FromJSON AnalyzeSentimentResponse Source # 
type Rep AnalyzeSentimentResponse Source # 
type Rep AnalyzeSentimentResponse = D1 (MetaData "AnalyzeSentimentResponse" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnalyzeSentimentResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_asrDocumentSentiment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Sentiment))) ((:*:) (S1 (MetaSel (Just Symbol "_asrSentences") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Sentence]))) (S1 (MetaSel (Just Symbol "_asrLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

analyzeSentimentResponse :: AnalyzeSentimentResponse Source #

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

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

asrDocumentSentiment :: Lens' AnalyzeSentimentResponse (Maybe Sentiment) Source #

The overall sentiment of the input document.

asrSentences :: Lens' AnalyzeSentimentResponse [Sentence] Source #

The sentiment for all the sentences in the document.

asrLanguage :: Lens' AnalyzeSentimentResponse (Maybe Text) Source #

The language of the text, which will be the same as the language specified in the request or, if not specified, the automatically-detected language. See `Document.language` field for more details.

AnalyzeEntitiesRequest

data AnalyzeEntitiesRequest Source #

The entity analysis request message.

See: analyzeEntitiesRequest smart constructor.

Instances

Eq AnalyzeEntitiesRequest Source # 
Data AnalyzeEntitiesRequest Source # 

Methods

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

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

toConstr :: AnalyzeEntitiesRequest -> Constr #

dataTypeOf :: AnalyzeEntitiesRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeEntitiesRequest Source # 
Generic AnalyzeEntitiesRequest Source # 
ToJSON AnalyzeEntitiesRequest Source # 
FromJSON AnalyzeEntitiesRequest Source # 
type Rep AnalyzeEntitiesRequest Source # 
type Rep AnalyzeEntitiesRequest = D1 (MetaData "AnalyzeEntitiesRequest" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnalyzeEntitiesRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aerEncodingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnalyzeEntitiesRequestEncodingType))) (S1 (MetaSel (Just Symbol "_aerDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Document)))))

analyzeEntitiesRequest :: AnalyzeEntitiesRequest Source #

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

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

aerEncodingType :: Lens' AnalyzeEntitiesRequest (Maybe AnalyzeEntitiesRequestEncodingType) Source #

The encoding type used by the API to calculate offsets.

AnalyzeEntitiesRequestEncodingType

data AnalyzeEntitiesRequestEncodingType Source #

The encoding type used by the API to calculate offsets.

Constructors

AERETNone

NONE If `EncodingType` is not specified, encoding-dependent information (such as `begin_offset`) will be set at `-1`.

AERETUTF8

UTF8 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-8 encoding of the input. C++ and Go are examples of languages that use this encoding natively.

AERETUTF16

UTF16 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-16 encoding of the input. Java and Javascript are examples of languages that use this encoding natively.

AERETUTF32

UTF32 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-32 encoding of the input. Python is an example of a language that uses this encoding natively.

Instances

Enum AnalyzeEntitiesRequestEncodingType Source # 
Eq AnalyzeEntitiesRequestEncodingType Source # 
Data AnalyzeEntitiesRequestEncodingType Source # 

Methods

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

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

toConstr :: AnalyzeEntitiesRequestEncodingType -> Constr #

dataTypeOf :: AnalyzeEntitiesRequestEncodingType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnalyzeEntitiesRequestEncodingType Source # 
Read AnalyzeEntitiesRequestEncodingType Source # 
Show AnalyzeEntitiesRequestEncodingType Source # 
Generic AnalyzeEntitiesRequestEncodingType Source # 
Hashable AnalyzeEntitiesRequestEncodingType Source # 
ToJSON AnalyzeEntitiesRequestEncodingType Source # 
FromJSON AnalyzeEntitiesRequestEncodingType Source # 
FromHttpApiData AnalyzeEntitiesRequestEncodingType Source # 
ToHttpApiData AnalyzeEntitiesRequestEncodingType Source # 
type Rep AnalyzeEntitiesRequestEncodingType Source # 
type Rep AnalyzeEntitiesRequestEncodingType = D1 (MetaData "AnalyzeEntitiesRequestEncodingType" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "AERETNone" PrefixI False) U1) (C1 (MetaCons "AERETUTF8" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AERETUTF16" PrefixI False) U1) (C1 (MetaCons "AERETUTF32" PrefixI False) U1)))

Entity

data Entity Source #

Represents a phrase in the text that is a known entity, such as a person, an organization, or location. The API associates information, such as salience and mentions, with entities.

See: entity smart constructor.

Instances

Eq Entity Source # 

Methods

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

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

Data Entity Source # 

Methods

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

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

toConstr :: Entity -> Constr #

dataTypeOf :: Entity -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Entity Source # 
Generic Entity Source # 

Associated Types

type Rep Entity :: * -> * #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

ToJSON Entity Source # 
FromJSON Entity Source # 
type Rep Entity Source # 

entity :: Entity Source #

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

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

eName :: Lens' Entity (Maybe Text) Source #

The representative name for the entity.

eSalience :: Lens' Entity (Maybe Double) Source #

The salience score associated with the entity in the [0, 1.0] range. The salience score for an entity provides information about the importance or centrality of that entity to the entire document text. Scores closer to 0 are less salient, while scores closer to 1.0 are highly salient.

eMetadata :: Lens' Entity (Maybe EntityMetadata) Source #

Metadata associated with the entity. Currently, Wikipedia URLs and Knowledge Graph MIDs are provided, if available. The associated keys are "wikipedia_url" and "mid", respectively.

eType :: Lens' Entity (Maybe EntityType) Source #

The entity type.

eMentions :: Lens' Entity [EntityMention] Source #

The mentions of this entity in the input document. The API currently supports proper noun mentions.

AnalyzeSyntaxResponse

data AnalyzeSyntaxResponse Source #

The syntax analysis response message.

See: analyzeSyntaxResponse smart constructor.

Instances

Eq AnalyzeSyntaxResponse Source # 
Data AnalyzeSyntaxResponse Source # 

Methods

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

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

toConstr :: AnalyzeSyntaxResponse -> Constr #

dataTypeOf :: AnalyzeSyntaxResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeSyntaxResponse Source # 
Generic AnalyzeSyntaxResponse Source # 
ToJSON AnalyzeSyntaxResponse Source # 
FromJSON AnalyzeSyntaxResponse Source # 
type Rep AnalyzeSyntaxResponse Source # 
type Rep AnalyzeSyntaxResponse = D1 (MetaData "AnalyzeSyntaxResponse" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "AnalyzeSyntaxResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aTokens") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Token]))) ((:*:) (S1 (MetaSel (Just Symbol "_aSentences") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Sentence]))) (S1 (MetaSel (Just Symbol "_aLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

analyzeSyntaxResponse :: AnalyzeSyntaxResponse Source #

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

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

aTokens :: Lens' AnalyzeSyntaxResponse [Token] Source #

Tokens, along with their syntactic information, in the input document.

aSentences :: Lens' AnalyzeSyntaxResponse [Sentence] Source #

Sentences in the input document.

aLanguage :: Lens' AnalyzeSyntaxResponse (Maybe Text) Source #

The language of the text, which will be the same as the language specified in the request or, if not specified, the automatically-detected language. See `Document.language` field for more details.

EntityMetadata

data EntityMetadata Source #

Metadata associated with the entity. Currently, Wikipedia URLs and Knowledge Graph MIDs are provided, if available. The associated keys are "wikipedia_url" and "mid", respectively.

See: entityMetadata smart constructor.

Instances

Eq EntityMetadata Source # 
Data EntityMetadata Source # 

Methods

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

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

toConstr :: EntityMetadata -> Constr #

dataTypeOf :: EntityMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EntityMetadata Source # 
Generic EntityMetadata Source # 

Associated Types

type Rep EntityMetadata :: * -> * #

ToJSON EntityMetadata Source # 
FromJSON EntityMetadata Source # 
type Rep EntityMetadata Source # 
type Rep EntityMetadata = D1 (MetaData "EntityMetadata" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" True) (C1 (MetaCons "EntityMetadata'" PrefixI True) (S1 (MetaSel (Just Symbol "_emAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))

entityMetadata Source #

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

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

PartOfSpeechAspect

data PartOfSpeechAspect Source #

The grammatical aspect.

Constructors

AspectUnknown

ASPECT_UNKNOWN Aspect is not applicable in the analyzed language or is not predicted.

Perfective

PERFECTIVE Perfective

Imperfective

IMPERFECTIVE Imperfective

Progressive

PROGRESSIVE Progressive

Instances

Enum PartOfSpeechAspect Source # 
Eq PartOfSpeechAspect Source # 
Data PartOfSpeechAspect Source # 

Methods

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

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

toConstr :: PartOfSpeechAspect -> Constr #

dataTypeOf :: PartOfSpeechAspect -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechAspect Source # 
Read PartOfSpeechAspect Source # 
Show PartOfSpeechAspect Source # 
Generic PartOfSpeechAspect Source # 
Hashable PartOfSpeechAspect Source # 
ToJSON PartOfSpeechAspect Source # 
FromJSON PartOfSpeechAspect Source # 
FromHttpApiData PartOfSpeechAspect Source # 
ToHttpApiData PartOfSpeechAspect Source # 
type Rep PartOfSpeechAspect Source # 
type Rep PartOfSpeechAspect = D1 (MetaData "PartOfSpeechAspect" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "AspectUnknown" PrefixI False) U1) (C1 (MetaCons "Perfective" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Imperfective" PrefixI False) U1) (C1 (MetaCons "Progressive" PrefixI False) U1)))

PartOfSpeech

data PartOfSpeech Source #

Represents part of speech information for a token. Parts of speech are as defined in http://www.lrec-conf.org/proceedings/lrec2012/pdf/274_Paper.pdf

See: partOfSpeech smart constructor.

Instances

Eq PartOfSpeech Source # 
Data PartOfSpeech Source # 

Methods

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

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

toConstr :: PartOfSpeech -> Constr #

dataTypeOf :: PartOfSpeech -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PartOfSpeech Source # 
Generic PartOfSpeech Source # 

Associated Types

type Rep PartOfSpeech :: * -> * #

ToJSON PartOfSpeech Source # 
FromJSON PartOfSpeech Source # 
type Rep PartOfSpeech Source # 
type Rep PartOfSpeech = D1 (MetaData "PartOfSpeech" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "PartOfSpeech'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_posProper") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechProper))) ((:*:) (S1 (MetaSel (Just Symbol "_posTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechTag))) (S1 (MetaSel (Just Symbol "_posPerson") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechPerson))))) ((:*:) (S1 (MetaSel (Just Symbol "_posAspect") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechAspect))) ((:*:) (S1 (MetaSel (Just Symbol "_posCase") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechCase))) (S1 (MetaSel (Just Symbol "_posGender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechGender)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_posReciprocity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechReciprocity))) ((:*:) (S1 (MetaSel (Just Symbol "_posNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechNumber))) (S1 (MetaSel (Just Symbol "_posVoice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechVoice))))) ((:*:) (S1 (MetaSel (Just Symbol "_posForm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechForm))) ((:*:) (S1 (MetaSel (Just Symbol "_posTense") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechTense))) (S1 (MetaSel (Just Symbol "_posMood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PartOfSpeechMood))))))))

partOfSpeech :: PartOfSpeech Source #

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

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

posProper :: Lens' PartOfSpeech (Maybe PartOfSpeechProper) Source #

The grammatical properness.

posTag :: Lens' PartOfSpeech (Maybe PartOfSpeechTag) Source #

The part of speech tag.

PartOfSpeechReciprocity

data PartOfSpeechReciprocity Source #

The grammatical reciprocity.

Constructors

ReciprocityUnknown

RECIPROCITY_UNKNOWN Reciprocity is not applicable in the analyzed language or is not predicted.

Reciprocal

RECIPROCAL Reciprocal

NonReciprocal

NON_RECIPROCAL Non-reciprocal

Instances

Enum PartOfSpeechReciprocity Source # 
Eq PartOfSpeechReciprocity Source # 
Data PartOfSpeechReciprocity Source # 

Methods

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

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

toConstr :: PartOfSpeechReciprocity -> Constr #

dataTypeOf :: PartOfSpeechReciprocity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechReciprocity Source # 
Read PartOfSpeechReciprocity Source # 
Show PartOfSpeechReciprocity Source # 
Generic PartOfSpeechReciprocity Source # 
Hashable PartOfSpeechReciprocity Source # 
ToJSON PartOfSpeechReciprocity Source # 
FromJSON PartOfSpeechReciprocity Source # 
FromHttpApiData PartOfSpeechReciprocity Source # 
ToHttpApiData PartOfSpeechReciprocity Source # 
type Rep PartOfSpeechReciprocity Source # 
type Rep PartOfSpeechReciprocity = D1 (MetaData "PartOfSpeechReciprocity" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) (C1 (MetaCons "ReciprocityUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "Reciprocal" PrefixI False) U1) (C1 (MetaCons "NonReciprocal" PrefixI False) U1)))

PartOfSpeechGender

data PartOfSpeechGender Source #

The grammatical gender.

Constructors

GenderUnknown

GENDER_UNKNOWN Gender is not applicable in the analyzed language or is not predicted.

Feminine

FEMININE Feminine

Masculine

MASCULINE Masculine

Neuter

NEUTER Neuter

Instances

Enum PartOfSpeechGender Source # 
Eq PartOfSpeechGender Source # 
Data PartOfSpeechGender Source # 

Methods

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

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

toConstr :: PartOfSpeechGender -> Constr #

dataTypeOf :: PartOfSpeechGender -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartOfSpeechGender Source # 
Read PartOfSpeechGender Source # 
Show PartOfSpeechGender Source # 
Generic PartOfSpeechGender Source # 
Hashable PartOfSpeechGender Source # 
ToJSON PartOfSpeechGender Source # 
FromJSON PartOfSpeechGender Source # 
FromHttpApiData PartOfSpeechGender Source # 
ToHttpApiData PartOfSpeechGender Source # 
type Rep PartOfSpeechGender Source # 
type Rep PartOfSpeechGender = D1 (MetaData "PartOfSpeechGender" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "GenderUnknown" PrefixI False) U1) (C1 (MetaCons "Feminine" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Masculine" PrefixI False) U1) (C1 (MetaCons "Neuter" PrefixI False) U1)))

AnalyzeSentimentRequestEncodingType

data AnalyzeSentimentRequestEncodingType Source #

The encoding type used by the API to calculate sentence offsets.

Constructors

ASRETNone

NONE If `EncodingType` is not specified, encoding-dependent information (such as `begin_offset`) will be set at `-1`.

ASRETUTF8

UTF8 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-8 encoding of the input. C++ and Go are examples of languages that use this encoding natively.

ASRETUTF16

UTF16 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-16 encoding of the input. Java and Javascript are examples of languages that use this encoding natively.

ASRETUTF32

UTF32 Encoding-dependent information (such as `begin_offset`) is calculated based on the UTF-32 encoding of the input. Python is an example of a language that uses this encoding natively.

Instances

Enum AnalyzeSentimentRequestEncodingType Source # 
Eq AnalyzeSentimentRequestEncodingType Source # 
Data AnalyzeSentimentRequestEncodingType Source # 

Methods

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

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

toConstr :: AnalyzeSentimentRequestEncodingType -> Constr #

dataTypeOf :: AnalyzeSentimentRequestEncodingType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnalyzeSentimentRequestEncodingType Source # 
Read AnalyzeSentimentRequestEncodingType Source # 
Show AnalyzeSentimentRequestEncodingType Source # 
Generic AnalyzeSentimentRequestEncodingType Source # 
Hashable AnalyzeSentimentRequestEncodingType Source # 
ToJSON AnalyzeSentimentRequestEncodingType Source # 
FromJSON AnalyzeSentimentRequestEncodingType Source # 
FromHttpApiData AnalyzeSentimentRequestEncodingType Source # 
ToHttpApiData AnalyzeSentimentRequestEncodingType Source # 
type Rep AnalyzeSentimentRequestEncodingType Source # 
type Rep AnalyzeSentimentRequestEncodingType = D1 (MetaData "AnalyzeSentimentRequestEncodingType" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) ((:+:) (C1 (MetaCons "ASRETNone" PrefixI False) U1) (C1 (MetaCons "ASRETUTF8" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ASRETUTF16" PrefixI False) U1) (C1 (MetaCons "ASRETUTF32" PrefixI False) U1)))

EntityMentionType

data EntityMentionType Source #

The type of the entity mention.

Constructors

EMTTypeUnknown

TYPE_UNKNOWN Unknown

EMTProper

PROPER Proper name

EMTCommon

COMMON Common noun (or noun compound)

Instances

Enum EntityMentionType Source # 
Eq EntityMentionType Source # 
Data EntityMentionType Source # 

Methods

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

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

toConstr :: EntityMentionType -> Constr #

dataTypeOf :: EntityMentionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EntityMentionType Source # 
Read EntityMentionType Source # 
Show EntityMentionType Source # 
Generic EntityMentionType Source # 
Hashable EntityMentionType Source # 
ToJSON EntityMentionType Source # 
FromJSON EntityMentionType Source # 
FromHttpApiData EntityMentionType Source # 
ToHttpApiData EntityMentionType Source # 
type Rep EntityMentionType Source # 
type Rep EntityMentionType = D1 (MetaData "EntityMentionType" "Network.Google.Language.Types.Sum" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) ((:+:) (C1 (MetaCons "EMTTypeUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "EMTProper" PrefixI False) U1) (C1 (MetaCons "EMTCommon" PrefixI False) U1)))

Sentence

data Sentence Source #

Represents a sentence in the input document.

See: sentence smart constructor.

Instances

Eq Sentence Source # 
Data Sentence Source # 

Methods

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

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

toConstr :: Sentence -> Constr #

dataTypeOf :: Sentence -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Sentence Source # 
Generic Sentence Source # 

Associated Types

type Rep Sentence :: * -> * #

Methods

from :: Sentence -> Rep Sentence x #

to :: Rep Sentence x -> Sentence #

ToJSON Sentence Source # 
FromJSON Sentence Source # 
type Rep Sentence Source # 
type Rep Sentence = D1 (MetaData "Sentence" "Network.Google.Language.Types.Product" "gogol-language-0.3.0-CtTe6JvFU50GV02GFrvgpP" False) (C1 (MetaCons "Sentence'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sSentiment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Sentiment))) (S1 (MetaSel (Just Symbol "_sText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextSpan)))))

sentence :: Sentence Source #

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

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

sSentiment :: Lens' Sentence (Maybe Sentiment) Source #

For calls to AnalyzeSentiment or if AnnotateTextRequest.Features.extract_document_sentiment is set to true, this field will contain the sentiment for the sentence.

sText :: Lens' Sentence (Maybe TextSpan) Source #

The sentence text.