gogol-commentanalyzer-0.5.0: Google Perspective Comment Analyzer 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.CommentAnalyzer

Contents

Description

The Perspective Comment Analyzer API provides information about the potential impact of a comment on a conversation (e.g. it can provide a score for the "toxicity" of a comment). Users can leverage the "SuggestCommentScore" method to submit corrections to improve Perspective over time. Users can set the "doNotStore" flag to ensure that all submitted comments are automatically deleted after scores are returned.

See: Perspective Comment Analyzer API Reference

Synopsis

Service Configuration

commentAnalyzerService :: ServiceConfig Source #

Default request referring to version v1alpha1 of the Perspective Comment Analyzer API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

userInfoEmailScope :: Proxy '["https://www.googleapis.com/auth/userinfo.email"] Source #

View your email address

API Declaration

type CommentAnalyzerAPI = CommentsSuggestscoreResource :<|> CommentsAnalyzeResource Source #

Represents the entirety of the methods and resources available for the Perspective Comment Analyzer API service.

Resources

commentanalyzer.comments.analyze

commentanalyzer.comments.suggestscore

Types

SpanScore

data SpanScore Source #

This is a single score for a given span of text.

See: spanScore smart constructor.

Instances
Eq SpanScore Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data SpanScore Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: SpanScore -> Constr #

dataTypeOf :: SpanScore -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpanScore Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic SpanScore Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep SpanScore :: Type -> Type #

ToJSON SpanScore Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON SpanScore Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SpanScore Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SpanScore = D1 (MetaData "SpanScore" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "SpanScore'" PrefixI True) (S1 (MetaSel (Just "_ssBegin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: (S1 (MetaSel (Just "_ssScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Score)) :*: S1 (MetaSel (Just "_ssEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

spanScore :: SpanScore Source #

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

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

ssBegin :: Lens' SpanScore (Maybe Int32) Source #

"begin" and "end" describe the span of the original text that the attribute score applies to. The values are the UTF-16 codepoint range. "end" is exclusive. For example, with the text "Hi there", the begin/end pair (0,2) describes the text "Hi". If "begin" and "end" are unset, the score applies to the full text.

ssScore :: Lens' SpanScore (Maybe Score) Source #

The score value.

AnalyzeCommentResponse

data AnalyzeCommentResponse Source #

The comment analysis response message.

See: analyzeCommentResponse smart constructor.

Instances
Eq AnalyzeCommentResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data AnalyzeCommentResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: AnalyzeCommentResponse -> Constr #

dataTypeOf :: AnalyzeCommentResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeCommentResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic AnalyzeCommentResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep AnalyzeCommentResponse :: Type -> Type #

ToJSON AnalyzeCommentResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON AnalyzeCommentResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AnalyzeCommentResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AnalyzeCommentResponse = D1 (MetaData "AnalyzeCommentResponse" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "AnalyzeCommentResponse'" PrefixI True) ((S1 (MetaSel (Just "_acrDetectedLanguages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_acrClientToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_acrLanguages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_acrAttributeScores") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnalyzeCommentResponseAttributeScores)))))

analyzeCommentResponse :: AnalyzeCommentResponse Source #

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

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

acrDetectedLanguages :: Lens' AnalyzeCommentResponse [Text] Source #

Contains the language as detected from the text content. If no language was specified in the request, the first (the most likely) language is used to select an appropriate model. Sorted in order of likelihood.

acrClientToken :: Lens' AnalyzeCommentResponse (Maybe Text) Source #

Same token from the original AnalyzeCommentRequest.

acrLanguages :: Lens' AnalyzeCommentResponse [Text] Source #

The language(s) requested by the client, as specified in the request. If the request did not specify any language, this will be empty and the detected_languages field will be populated.

acrAttributeScores :: Lens' AnalyzeCommentResponse (Maybe AnalyzeCommentResponseAttributeScores) Source #

Scores for the requested attributes. The map keys are attribute names (same as the requested_attribute field in AnalyzeCommentRequest, for example "ATTACK_ON_AUTHOR", "INFLAMMATORY", etc).

SuggestCommentScoreResponse

data SuggestCommentScoreResponse Source #

The comment score suggestion response message.

See: suggestCommentScoreResponse smart constructor.

Instances
Eq SuggestCommentScoreResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data SuggestCommentScoreResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: SuggestCommentScoreResponse -> Constr #

dataTypeOf :: SuggestCommentScoreResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SuggestCommentScoreResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic SuggestCommentScoreResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep SuggestCommentScoreResponse :: Type -> Type #

ToJSON SuggestCommentScoreResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON SuggestCommentScoreResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SuggestCommentScoreResponse Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SuggestCommentScoreResponse = D1 (MetaData "SuggestCommentScoreResponse" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "SuggestCommentScoreResponse'" PrefixI True) (S1 (MetaSel (Just "_scsrDetectedLanguages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 (MetaSel (Just "_scsrClientToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_scsrRequestedLanguages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))

suggestCommentScoreResponse :: SuggestCommentScoreResponse Source #

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

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

scsrDetectedLanguages :: Lens' SuggestCommentScoreResponse [Text] Source #

The list of languages detected from the comment text.

scsrClientToken :: Lens' SuggestCommentScoreResponse (Maybe Text) Source #

Same token from the original SuggestCommentScoreRequest.

scsrRequestedLanguages :: Lens' SuggestCommentScoreResponse [Text] Source #

The list of languages provided in the request.

Context

data Context Source #

Context is typically something that a Comment is referencing or replying to (such as an article, or previous comment). Note: Populate only ONE OF the following fields. The oneof syntax cannot be used because that would require nesting entries inside another message and breaking backwards compatibility. The server will return an error if more than one of the following fields is present.

See: context smart constructor.

Instances
Eq Context Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

Data Context Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: Context -> Constr #

dataTypeOf :: Context -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Context Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic Context Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep Context :: Type -> Type #

Methods

from :: Context -> Rep Context x #

to :: Rep Context x -> Context #

ToJSON Context Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON Context Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep Context Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep Context = D1 (MetaData "Context" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "Context'" PrefixI True) (S1 (MetaSel (Just "_cEntries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TextEntry])) :*: S1 (MetaSel (Just "_cArticleAndParentComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ArticleAndParentComment))))

context :: Context Source #

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

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

cEntries :: Lens' Context [TextEntry] Source #

A list of messages. For example, a linear comments section or forum thread.

cArticleAndParentComment :: Lens' Context (Maybe ArticleAndParentComment) Source #

Information about the source for which the original comment was made, and any parent comment info.

Score

data Score Source #

Analysis scores are described by a value and a ScoreType.

See: score smart constructor.

Instances
Eq Score Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

Data Score Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: Score -> Constr #

dataTypeOf :: Score -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Score Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

showsPrec :: Int -> Score -> ShowS #

show :: Score -> String #

showList :: [Score] -> ShowS #

Generic Score Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep Score :: Type -> Type #

Methods

from :: Score -> Rep Score x #

to :: Rep Score x -> Score #

ToJSON Score Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON Score Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep Score Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep Score = D1 (MetaData "Score" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "Score'" PrefixI True) (S1 (MetaSel (Just "_sValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_sType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ScoreType))))

score :: Score Source #

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

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

sValue :: Lens' Score (Maybe Double) Source #

Score value. Semantics described by type below.

sType :: Lens' Score (Maybe ScoreType) Source #

The type of the above value.

ArticleAndParentComment

data ArticleAndParentComment Source #

A type of context specific to a comment left on a single-threaded comment message board, where comments are either a top level comment or the child of a top level comment.

See: articleAndParentComment smart constructor.

Instances
Eq ArticleAndParentComment Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data ArticleAndParentComment Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: ArticleAndParentComment -> Constr #

dataTypeOf :: ArticleAndParentComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ArticleAndParentComment Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic ArticleAndParentComment Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep ArticleAndParentComment :: Type -> Type #

ToJSON ArticleAndParentComment Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON ArticleAndParentComment Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep ArticleAndParentComment Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep ArticleAndParentComment = D1 (MetaData "ArticleAndParentComment" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "ArticleAndParentComment'" PrefixI True) (S1 (MetaSel (Just "_aapcArticle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextEntry)) :*: S1 (MetaSel (Just "_aapcParentComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextEntry))))

articleAndParentComment :: ArticleAndParentComment Source #

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

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

aapcArticle :: Lens' ArticleAndParentComment (Maybe TextEntry) Source #

The source content about which the comment was made (article text, article summary, video transcript, etc).

aapcParentComment :: Lens' ArticleAndParentComment (Maybe TextEntry) Source #

Refers to text that is a direct parent of the source comment, such as in a one-deep threaded message board. This field will only be present for comments that are replies to other comments and will not be populated for direct comments on the article_text.

AttributeParameters

data AttributeParameters Source #

Configurable parameters for attribute scoring.

See: attributeParameters smart constructor.

Instances
Eq AttributeParameters Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data AttributeParameters Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: AttributeParameters -> Constr #

dataTypeOf :: AttributeParameters -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AttributeParameters Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic AttributeParameters Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep AttributeParameters :: Type -> Type #

ToJSON AttributeParameters Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON AttributeParameters Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AttributeParameters Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AttributeParameters = D1 (MetaData "AttributeParameters" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "AttributeParameters'" PrefixI True) (S1 (MetaSel (Just "_apScoreThreshold") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_apScoreType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AttributeParametersScoreType))))

attributeParameters :: AttributeParameters Source #

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

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

apScoreThreshold :: Lens' AttributeParameters (Maybe Double) Source #

Don't return scores for this attribute that are below this threshold. If unset, a default threshold will be applied. A FloatValue wrapper is used to distinguish between 0 vs. default/unset.

apScoreType :: Lens' AttributeParameters (Maybe AttributeParametersScoreType) Source #

What type of scores to return. If unset, defaults to probability scores.

TextEntry

data TextEntry Source #

Represents a body of text.

See: textEntry smart constructor.

Instances
Eq TextEntry Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data TextEntry Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: TextEntry -> Constr #

dataTypeOf :: TextEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TextEntry Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic TextEntry Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep TextEntry :: Type -> Type #

ToJSON TextEntry Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON TextEntry Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep TextEntry Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep TextEntry = D1 (MetaData "TextEntry" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "TextEntry'" PrefixI True) (S1 (MetaSel (Just "_teText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_teType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextEntryType))))

textEntry :: TextEntry Source #

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

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

teText :: Lens' TextEntry (Maybe Text) Source #

UTF-8 encoded text.

teType :: Lens' TextEntry (Maybe TextEntryType) Source #

Type of the text field.

AttributeScores

data AttributeScores Source #

This holds score values for a single attribute. It contains both per-span scores as well as an overall summary score..

See: attributeScores smart constructor.

Instances
Eq AttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data AttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: AttributeScores -> Constr #

dataTypeOf :: AttributeScores -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic AttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep AttributeScores :: Type -> Type #

ToJSON AttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON AttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AttributeScores = D1 (MetaData "AttributeScores" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "AttributeScores'" PrefixI True) (S1 (MetaSel (Just "_asSummaryScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Score)) :*: S1 (MetaSel (Just "_asSpanScores") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SpanScore]))))

attributeScores :: AttributeScores Source #

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

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

asSummaryScore :: Lens' AttributeScores (Maybe Score) Source #

Overall score for comment as a whole.

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances
Enum Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

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

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

Data Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

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

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

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

compare :: Xgafv -> Xgafv -> Ordering #

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

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

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

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

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Associated Types

type Rep Xgafv :: Type -> Type #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.CommentAnalyzer.Types.Sum" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "X1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "X2" PrefixI False) (U1 :: Type -> Type))

ScoreType

data ScoreType Source #

The type of the above value.

Constructors

ScoreTypeUnspecified

SCORE_TYPE_UNSPECIFIED Unspecified. Defaults to PROBABILITY scores if available, and otherwise RAW. Every model has a RAW score.

Probability

PROBABILITY Probability scores are in the range [0, 1] and indicate level of confidence in the attribute label.

StdDevScore

STD_DEV_SCORE Standard deviation scores are in the range (-inf, +inf).

Percentile

PERCENTILE Percentile scores are in the range [0, 1] and indicate the percentile of the raw score, normalized with a test dataset. This is not generally recommended, as the normalization is dependent on the dataset used, which may not match other usecases.

Raw

RAW Raw scores are the raw values from the model, and may take any value. This is primarily for debugging/testing, and not generally recommended.

Instances
Enum ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Eq ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Data ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

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

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

toConstr :: ScoreType -> Constr #

dataTypeOf :: ScoreType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Read ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Show ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Generic ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Associated Types

type Rep ScoreType :: Type -> Type #

Hashable ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

ToJSON ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromJSON ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromHttpApiData ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

ToHttpApiData ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep ScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep ScoreType = D1 (MetaData "ScoreType" "Network.Google.CommentAnalyzer.Types.Sum" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) ((C1 (MetaCons "ScoreTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Probability" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StdDevScore" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Percentile" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Raw" PrefixI False) (U1 :: Type -> Type))))

AnalyzeCommentResponseAttributeScores

data AnalyzeCommentResponseAttributeScores Source #

Scores for the requested attributes. The map keys are attribute names (same as the requested_attribute field in AnalyzeCommentRequest, for example "ATTACK_ON_AUTHOR", "INFLAMMATORY", etc).

See: analyzeCommentResponseAttributeScores smart constructor.

Instances
Eq AnalyzeCommentResponseAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data AnalyzeCommentResponseAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: AnalyzeCommentResponseAttributeScores -> Constr #

dataTypeOf :: AnalyzeCommentResponseAttributeScores -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeCommentResponseAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic AnalyzeCommentResponseAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

ToJSON AnalyzeCommentResponseAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON AnalyzeCommentResponseAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AnalyzeCommentResponseAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AnalyzeCommentResponseAttributeScores = D1 (MetaData "AnalyzeCommentResponseAttributeScores" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" True) (C1 (MetaCons "AnalyzeCommentResponseAttributeScores'" PrefixI True) (S1 (MetaSel (Just "_acrasAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text AttributeScores))))

analyzeCommentResponseAttributeScores Source #

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

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

SuggestCommentScoreRequest

data SuggestCommentScoreRequest Source #

The comment score suggestion request message.

See: suggestCommentScoreRequest smart constructor.

Instances
Eq SuggestCommentScoreRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data SuggestCommentScoreRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: SuggestCommentScoreRequest -> Constr #

dataTypeOf :: SuggestCommentScoreRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SuggestCommentScoreRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic SuggestCommentScoreRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep SuggestCommentScoreRequest :: Type -> Type #

ToJSON SuggestCommentScoreRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON SuggestCommentScoreRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SuggestCommentScoreRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SuggestCommentScoreRequest = D1 (MetaData "SuggestCommentScoreRequest" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "SuggestCommentScoreRequest'" PrefixI True) ((S1 (MetaSel (Just "_sContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Context)) :*: (S1 (MetaSel (Just "_sClientToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_sLanguages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))) :*: ((S1 (MetaSel (Just "_sAttributeScores") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SuggestCommentScoreRequestAttributeScores)) :*: S1 (MetaSel (Just "_sSessionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_sComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextEntry)) :*: S1 (MetaSel (Just "_sCommUnityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

suggestCommentScoreRequest :: SuggestCommentScoreRequest Source #

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

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

sClientToken :: Lens' SuggestCommentScoreRequest (Maybe Text) Source #

Opaque token that is echoed from the request to the response.

sLanguages :: Lens' SuggestCommentScoreRequest [Text] Source #

The language(s) of the comment and context (if none are specified, the language is automatically detected). If multiple languages are specified, the text is checked in all of them that are supported. Both ISO and BCP-47 language codes are accepted. Current Language Restrictions: * Only English text ("en") is supported. If none of the languages specified by the caller are supported, an `UNIMPLEMENTED` error is returned.

sAttributeScores :: Lens' SuggestCommentScoreRequest (Maybe SuggestCommentScoreRequestAttributeScores) Source #

Attribute scores for the comment. The map keys are attribute names, same as the requested_attribute field in AnalyzeCommentRequest (for example "ATTACK_ON_AUTHOR", "INFLAMMATORY", etc.). This field has the same type as the `attribute_scores` field in AnalyzeCommentResponse. To specify an overall attribute score for the entire comment as a whole, use the `summary_score` field of the mapped AttributeScores object. To specify scores on specific subparts of the comment, use the `span_scores` field. All SpanScore objects must have begin and end fields set. All Score objects must be explicitly set (for binary classification, use the score values 0 and 1). If Score objects don't include a ScoreType, `PROBABILITY` is assumed. `attribute_scores` must not be empty. The mapped AttributeScores objects also must not be empty. An `INVALID_ARGUMENT` error is returned for all malformed requests.

sSessionId :: Lens' SuggestCommentScoreRequest (Maybe Text) Source #

Session ID. Used to join related RPCs into a single session. For example, an interactive tool that calls both the AnalyzeComment and SuggestCommentScore RPCs should set all invocations of both RPCs to the same Session ID, typically a random 64-bit integer.

sCommUnityId :: Lens' SuggestCommentScoreRequest (Maybe Text) Source #

Optional identifier associating this comment score suggestion with a particular sub-community. Different communities may have different norms and rules. Specifying this value enables training community-specific models.

AttributeParametersScoreType

data AttributeParametersScoreType Source #

What type of scores to return. If unset, defaults to probability scores.

Constructors

APSTScoreTypeUnspecified

SCORE_TYPE_UNSPECIFIED Unspecified. Defaults to PROBABILITY scores if available, and otherwise RAW. Every model has a RAW score.

APSTProbability

PROBABILITY Probability scores are in the range [0, 1] and indicate level of confidence in the attribute label.

APSTStdDevScore

STD_DEV_SCORE Standard deviation scores are in the range (-inf, +inf).

APSTPercentile

PERCENTILE Percentile scores are in the range [0, 1] and indicate the percentile of the raw score, normalized with a test dataset. This is not generally recommended, as the normalization is dependent on the dataset used, which may not match other usecases.

APSTRaw

RAW Raw scores are the raw values from the model, and may take any value. This is primarily for debugging/testing, and not generally recommended.

Instances
Enum AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Eq AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Data AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

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

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

toConstr :: AttributeParametersScoreType -> Constr #

dataTypeOf :: AttributeParametersScoreType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Read AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Show AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Generic AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Associated Types

type Rep AttributeParametersScoreType :: Type -> Type #

Hashable AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

ToJSON AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromJSON AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromHttpApiData AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

ToHttpApiData AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep AttributeParametersScoreType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep AttributeParametersScoreType = D1 (MetaData "AttributeParametersScoreType" "Network.Google.CommentAnalyzer.Types.Sum" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) ((C1 (MetaCons "APSTScoreTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "APSTProbability" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "APSTStdDevScore" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "APSTPercentile" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "APSTRaw" PrefixI False) (U1 :: Type -> Type))))

AnalyzeCommentRequest

data AnalyzeCommentRequest Source #

The comment analysis request message.

See: analyzeCommentRequest smart constructor.

Instances
Eq AnalyzeCommentRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data AnalyzeCommentRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: AnalyzeCommentRequest -> Constr #

dataTypeOf :: AnalyzeCommentRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeCommentRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic AnalyzeCommentRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Associated Types

type Rep AnalyzeCommentRequest :: Type -> Type #

ToJSON AnalyzeCommentRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON AnalyzeCommentRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AnalyzeCommentRequest Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

analyzeCommentRequest :: AnalyzeCommentRequest Source #

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

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

aContext :: Lens' AnalyzeCommentRequest (Maybe Context) Source #

The context of the comment.

aClientToken :: Lens' AnalyzeCommentRequest (Maybe Text) Source #

Opaque token that is echoed from the request to the response.

aSpanAnnotations :: Lens' AnalyzeCommentRequest (Maybe Bool) Source #

An advisory parameter that will return span annotations if the model is capable of providing scores with sub-comment resolution. This will likely increase the size of the returned message.

aDoNotStore :: Lens' AnalyzeCommentRequest (Maybe Bool) Source #

Do not store the comment or context sent in this request. By default, the service may store comments/context for debugging purposes.

aLanguages :: Lens' AnalyzeCommentRequest [Text] Source #

The language(s) of the comment and context (if none are specified, the language is automatically detected). If multiple languages are specified, the text is checked in all of them that are supported. Both ISO and BCP-47 language codes are accepted. Current Language Restrictions: * Only English text ("en") is supported. If none of the languages specified by the caller are supported, an `UNIMPLEMENTED` error is returned.

aRequestedAttributes :: Lens' AnalyzeCommentRequest (Maybe AnalyzeCommentRequestRequestedAttributes) Source #

Specification of requested attributes. The AttributeParameters serve as configuration for each associated attribute. The map keys are attribute names. The following attributes are available: "ATTACK_ON_AUTHOR" - Attack on author of original article or post. "ATTACK_ON_COMMENTER" - Attack on fellow commenter. "ATTACK_ON_PUBLISHER" - Attack on publisher of article/post. "INCOHERENT" - Difficult to understand, nonsensical. "INFLAMMATORY" - Intending to provoke or inflame. "OBSCENE" - Obscene, such as cursing. "OFF_TOPIC" - Not related to the original topic. "SPAM" - Commercial/advertising spam content. "UNSUBSTANTIAL" - Trivial.

aSessionId :: Lens' AnalyzeCommentRequest (Maybe Text) Source #

Session ID. Used to join related RPCs into a single session. For example, an interactive tool that calls both the AnalyzeComment and SuggestCommentScore RPCs should set all invocations of both RPCs to the same Session ID, typically a random 64-bit integer.

aCommUnityId :: Lens' AnalyzeCommentRequest (Maybe Text) Source #

Optional identifier associating this AnalyzeCommentRequest with a particular client's community. Different communities may have different norms and rules. Specifying this value enables us to explore building community-specific models for clients.

SuggestCommentScoreRequestAttributeScores

data SuggestCommentScoreRequestAttributeScores Source #

Attribute scores for the comment. The map keys are attribute names, same as the requested_attribute field in AnalyzeCommentRequest (for example "ATTACK_ON_AUTHOR", "INFLAMMATORY", etc.). This field has the same type as the `attribute_scores` field in AnalyzeCommentResponse. To specify an overall attribute score for the entire comment as a whole, use the `summary_score` field of the mapped AttributeScores object. To specify scores on specific subparts of the comment, use the `span_scores` field. All SpanScore objects must have begin and end fields set. All Score objects must be explicitly set (for binary classification, use the score values 0 and 1). If Score objects don't include a ScoreType, `PROBABILITY` is assumed. `attribute_scores` must not be empty. The mapped AttributeScores objects also must not be empty. An `INVALID_ARGUMENT` error is returned for all malformed requests.

See: suggestCommentScoreRequestAttributeScores smart constructor.

Instances
Eq SuggestCommentScoreRequestAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data SuggestCommentScoreRequestAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: SuggestCommentScoreRequestAttributeScores -> Constr #

dataTypeOf :: SuggestCommentScoreRequestAttributeScores -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SuggestCommentScoreRequestAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic SuggestCommentScoreRequestAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

ToJSON SuggestCommentScoreRequestAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON SuggestCommentScoreRequestAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SuggestCommentScoreRequestAttributeScores Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep SuggestCommentScoreRequestAttributeScores = D1 (MetaData "SuggestCommentScoreRequestAttributeScores" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" True) (C1 (MetaCons "SuggestCommentScoreRequestAttributeScores'" PrefixI True) (S1 (MetaSel (Just "_scsrasAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text AttributeScores))))

suggestCommentScoreRequestAttributeScores Source #

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

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

AnalyzeCommentRequestRequestedAttributes

data AnalyzeCommentRequestRequestedAttributes Source #

Specification of requested attributes. The AttributeParameters serve as configuration for each associated attribute. The map keys are attribute names. The following attributes are available: "ATTACK_ON_AUTHOR" - Attack on author of original article or post. "ATTACK_ON_COMMENTER" - Attack on fellow commenter. "ATTACK_ON_PUBLISHER" - Attack on publisher of article/post. "INCOHERENT" - Difficult to understand, nonsensical. "INFLAMMATORY" - Intending to provoke or inflame. "OBSCENE" - Obscene, such as cursing. "OFF_TOPIC" - Not related to the original topic. "SPAM" - Commercial/advertising spam content. "UNSUBSTANTIAL" - Trivial.

See: analyzeCommentRequestRequestedAttributes smart constructor.

Instances
Eq AnalyzeCommentRequestRequestedAttributes Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Data AnalyzeCommentRequestRequestedAttributes Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Methods

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

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

toConstr :: AnalyzeCommentRequestRequestedAttributes -> Constr #

dataTypeOf :: AnalyzeCommentRequestRequestedAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnalyzeCommentRequestRequestedAttributes Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

Generic AnalyzeCommentRequestRequestedAttributes Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

ToJSON AnalyzeCommentRequestRequestedAttributes Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

FromJSON AnalyzeCommentRequestRequestedAttributes Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AnalyzeCommentRequestRequestedAttributes Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Product

type Rep AnalyzeCommentRequestRequestedAttributes = D1 (MetaData "AnalyzeCommentRequestRequestedAttributes" "Network.Google.CommentAnalyzer.Types.Product" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" True) (C1 (MetaCons "AnalyzeCommentRequestRequestedAttributes'" PrefixI True) (S1 (MetaSel (Just "_acrraAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text AttributeParameters))))

analyzeCommentRequestRequestedAttributes Source #

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

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

TextEntryType

data TextEntryType Source #

Type of the text field.

Constructors

TextTypeUnspecified

TEXT_TYPE_UNSPECIFIED The content type is not specified. Text will be interpreted as plain text by default.

PlainText

PLAIN_TEXT Plain text.

HTML

HTML HTML.

Instances
Enum TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Eq TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Data TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Methods

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

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

toConstr :: TextEntryType -> Constr #

dataTypeOf :: TextEntryType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Read TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Show TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Generic TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

Associated Types

type Rep TextEntryType :: Type -> Type #

Hashable TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

ToJSON TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromJSON TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

FromHttpApiData TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

ToHttpApiData TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep TextEntryType Source # 
Instance details

Defined in Network.Google.CommentAnalyzer.Types.Sum

type Rep TextEntryType = D1 (MetaData "TextEntryType" "Network.Google.CommentAnalyzer.Types.Sum" "gogol-commentanalyzer-0.5.0-8SuTksTsIruKQ8nHrD8kVJ" False) (C1 (MetaCons "TextTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PlainText" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HTML" PrefixI False) (U1 :: Type -> Type)))