amazonka-comprehend-1.6.0: Amazon Comprehend SDK.

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

Network.AWS.Comprehend

Contents

Description

Amazon Comprehend is an AWS service for gaining insight into the content of documents. Use these actions to determine the topics contained in your documents, the topics they discuss, the predominant sentiment expressed in them, the predominant language used, and more.

Synopsis

Service Configuration

comprehend :: Service Source #

API version 2017-11-27 of the Amazon Comprehend SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by Comprehend.

InvalidRequestException

TooManyRequestsException

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

The number of requests exceeds the limit. Resubmit your request later.

InternalServerException

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

An internal server error occurred. Retry your request.

BatchSizeLimitExceededException

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

The number of documents in the request exceeds the limit of 25. Try your request again with fewer documents.

UnsupportedLanguageException

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

Amazon Comprehend can't process the language of the input text. For all APIs except DetectDominantLanguage , Amazon Comprehend accepts only English or Spanish text. For the DetectDominantLanguage API, Amazon Comprehend detects 100 languages. For a list of languages, see 'how-languages'

JobNotFoundException

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

The specified job was not found. Check the job ID and try again.

InvalidFilterException

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

The filter specified for the ListTopicDetectionJobs operation is invalid. Specify a different filter.

TextSizeLimitExceededException

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

The size of the input text exceeds the limit. Use a smaller document.

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

BatchDetectSentiment

StartTopicsDetectionJob

BatchDetectKeyPhrases

DetectSentiment

BatchDetectEntities

DetectDominantLanguage

DescribeTopicsDetectionJob

DetectEntities

ListTopicsDetectionJobs (Paginated)

BatchDetectDominantLanguage

DetectKeyPhrases

Types

EntityType

data EntityType Source #

Instances

Bounded EntityType Source # 
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 # 
FromJSON EntityType Source # 
NFData EntityType Source # 

Methods

rnf :: EntityType -> () #

ToHeader EntityType Source # 
ToQuery EntityType Source # 
ToByteString EntityType Source # 
FromText EntityType Source # 
ToText EntityType Source # 

Methods

toText :: EntityType -> Text #

type Rep EntityType Source # 
type Rep EntityType = D1 * (MetaData "EntityType" "Network.AWS.Comprehend.Types.Sum" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CommercialItem" PrefixI False) (U1 *)) (C1 * (MetaCons "Date" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Event" PrefixI False) (U1 *)) (C1 * (MetaCons "Location" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Organization" PrefixI False) (U1 *)) (C1 * (MetaCons "Other" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Person" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Quantity" PrefixI False) (U1 *)) (C1 * (MetaCons "Title" PrefixI False) (U1 *))))))

InputFormat

data InputFormat Source #

Instances

Bounded InputFormat Source # 
Enum InputFormat Source # 
Eq InputFormat Source # 
Data InputFormat Source # 

Methods

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

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

toConstr :: InputFormat -> Constr #

dataTypeOf :: InputFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InputFormat Source # 
Read InputFormat Source # 
Show InputFormat Source # 
Generic InputFormat Source # 

Associated Types

type Rep InputFormat :: * -> * #

Hashable InputFormat Source # 
ToJSON InputFormat Source # 
FromJSON InputFormat Source # 
NFData InputFormat Source # 

Methods

rnf :: InputFormat -> () #

ToHeader InputFormat Source # 
ToQuery InputFormat Source # 
ToByteString InputFormat Source # 
FromText InputFormat Source # 
ToText InputFormat Source # 

Methods

toText :: InputFormat -> Text #

type Rep InputFormat Source # 
type Rep InputFormat = D1 * (MetaData "InputFormat" "Network.AWS.Comprehend.Types.Sum" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) ((:+:) * (C1 * (MetaCons "OneDocPerFile" PrefixI False) (U1 *)) (C1 * (MetaCons "OneDocPerLine" PrefixI False) (U1 *)))

JobStatus

data JobStatus Source #

Instances

Bounded JobStatus Source # 
Enum JobStatus Source # 
Eq JobStatus Source # 
Data JobStatus Source # 

Methods

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

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

toConstr :: JobStatus -> Constr #

dataTypeOf :: JobStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JobStatus Source # 
Read JobStatus Source # 
Show JobStatus Source # 
Generic JobStatus Source # 

Associated Types

type Rep JobStatus :: * -> * #

Hashable JobStatus Source # 
ToJSON JobStatus Source # 
FromJSON JobStatus Source # 
NFData JobStatus Source # 

Methods

rnf :: JobStatus -> () #

ToHeader JobStatus Source # 
ToQuery JobStatus Source # 
ToByteString JobStatus Source # 

Methods

toBS :: JobStatus -> ByteString #

FromText JobStatus Source # 
ToText JobStatus Source # 

Methods

toText :: JobStatus -> Text #

type Rep JobStatus Source # 
type Rep JobStatus = D1 * (MetaData "JobStatus" "Network.AWS.Comprehend.Types.Sum" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Completed" PrefixI False) (U1 *)) (C1 * (MetaCons "Failed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "InProgress" PrefixI False) (U1 *)) (C1 * (MetaCons "Submitted" PrefixI False) (U1 *))))

LanguageCode

data LanguageCode Source #

Constructors

EN 
ES 

Instances

Bounded LanguageCode Source # 
Enum LanguageCode Source # 
Eq LanguageCode Source # 
Data LanguageCode Source # 

Methods

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

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

toConstr :: LanguageCode -> Constr #

dataTypeOf :: LanguageCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LanguageCode Source # 
Read LanguageCode Source # 
Show LanguageCode Source # 
Generic LanguageCode Source # 

Associated Types

type Rep LanguageCode :: * -> * #

Hashable LanguageCode Source # 
ToJSON LanguageCode Source # 
NFData LanguageCode Source # 

Methods

rnf :: LanguageCode -> () #

ToHeader LanguageCode Source # 
ToQuery LanguageCode Source # 
ToByteString LanguageCode Source # 
FromText LanguageCode Source # 
ToText LanguageCode Source # 

Methods

toText :: LanguageCode -> Text #

type Rep LanguageCode Source # 
type Rep LanguageCode = D1 * (MetaData "LanguageCode" "Network.AWS.Comprehend.Types.Sum" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) ((:+:) * (C1 * (MetaCons "EN" PrefixI False) (U1 *)) (C1 * (MetaCons "ES" PrefixI False) (U1 *)))

SentimentType

data SentimentType Source #

Constructors

Mixed 
Negative 
Neutral 
Positive 

Instances

Bounded SentimentType Source # 
Enum SentimentType Source # 
Eq SentimentType Source # 
Data SentimentType Source # 

Methods

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

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

toConstr :: SentimentType -> Constr #

dataTypeOf :: SentimentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SentimentType Source # 
Read SentimentType Source # 
Show SentimentType Source # 
Generic SentimentType Source # 

Associated Types

type Rep SentimentType :: * -> * #

Hashable SentimentType Source # 
FromJSON SentimentType Source # 
NFData SentimentType Source # 

Methods

rnf :: SentimentType -> () #

ToHeader SentimentType Source # 
ToQuery SentimentType Source # 
ToByteString SentimentType Source # 
FromText SentimentType Source # 
ToText SentimentType Source # 

Methods

toText :: SentimentType -> Text #

type Rep SentimentType Source # 
type Rep SentimentType = D1 * (MetaData "SentimentType" "Network.AWS.Comprehend.Types.Sum" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Mixed" PrefixI False) (U1 *)) (C1 * (MetaCons "Negative" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Neutral" PrefixI False) (U1 *)) (C1 * (MetaCons "Positive" PrefixI False) (U1 *))))

BatchDetectDominantLanguageItemResult

data BatchDetectDominantLanguageItemResult Source #

The result of calling the operation. The operation returns one object for each document that is successfully processed by the operation.

See: batchDetectDominantLanguageItemResult smart constructor.

Instances

Eq BatchDetectDominantLanguageItemResult Source # 
Data BatchDetectDominantLanguageItemResult Source # 

Methods

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

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

toConstr :: BatchDetectDominantLanguageItemResult -> Constr #

dataTypeOf :: BatchDetectDominantLanguageItemResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BatchDetectDominantLanguageItemResult Source # 
Show BatchDetectDominantLanguageItemResult Source # 
Generic BatchDetectDominantLanguageItemResult Source # 
Hashable BatchDetectDominantLanguageItemResult Source # 
FromJSON BatchDetectDominantLanguageItemResult Source # 
NFData BatchDetectDominantLanguageItemResult Source # 
type Rep BatchDetectDominantLanguageItemResult Source # 
type Rep BatchDetectDominantLanguageItemResult = D1 * (MetaData "BatchDetectDominantLanguageItemResult" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "BatchDetectDominantLanguageItemResult'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bddlirLanguages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [DominantLanguage]))) (S1 * (MetaSel (Just Symbol "_bddlirIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))

batchDetectDominantLanguageItemResult :: BatchDetectDominantLanguageItemResult Source #

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

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

bddlirLanguages :: Lens' BatchDetectDominantLanguageItemResult [DominantLanguage] Source #

One or more DominantLanguage objects describing the dominant languages in the document.

bddlirIndex :: Lens' BatchDetectDominantLanguageItemResult (Maybe Int) Source #

The zero-based index of the document in the input list.

BatchDetectEntitiesItemResult

data BatchDetectEntitiesItemResult Source #

The result of calling the operation. The operation returns one object for each document that is successfully processed by the operation.

See: batchDetectEntitiesItemResult smart constructor.

Instances

Eq BatchDetectEntitiesItemResult Source # 
Data BatchDetectEntitiesItemResult Source # 

Methods

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

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

toConstr :: BatchDetectEntitiesItemResult -> Constr #

dataTypeOf :: BatchDetectEntitiesItemResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BatchDetectEntitiesItemResult Source # 
Show BatchDetectEntitiesItemResult Source # 
Generic BatchDetectEntitiesItemResult Source # 
Hashable BatchDetectEntitiesItemResult Source # 
FromJSON BatchDetectEntitiesItemResult Source # 
NFData BatchDetectEntitiesItemResult Source # 
type Rep BatchDetectEntitiesItemResult Source # 
type Rep BatchDetectEntitiesItemResult = D1 * (MetaData "BatchDetectEntitiesItemResult" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "BatchDetectEntitiesItemResult'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdeirEntities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Entity]))) (S1 * (MetaSel (Just Symbol "_bdeirIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))

batchDetectEntitiesItemResult :: BatchDetectEntitiesItemResult Source #

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

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

  • bdeirEntities - One or more Entity objects, one for each entity detected in the document.
  • bdeirIndex - The zero-based index of the document in the input list.

bdeirEntities :: Lens' BatchDetectEntitiesItemResult [Entity] Source #

One or more Entity objects, one for each entity detected in the document.

bdeirIndex :: Lens' BatchDetectEntitiesItemResult (Maybe Int) Source #

The zero-based index of the document in the input list.

BatchDetectKeyPhrasesItemResult

data BatchDetectKeyPhrasesItemResult Source #

The result of calling the operation. The operation returns one object for each document that is successfully processed by the operation.

See: batchDetectKeyPhrasesItemResult smart constructor.

Instances

Eq BatchDetectKeyPhrasesItemResult Source # 
Data BatchDetectKeyPhrasesItemResult Source # 

Methods

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

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

toConstr :: BatchDetectKeyPhrasesItemResult -> Constr #

dataTypeOf :: BatchDetectKeyPhrasesItemResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BatchDetectKeyPhrasesItemResult Source # 
Show BatchDetectKeyPhrasesItemResult Source # 
Generic BatchDetectKeyPhrasesItemResult Source # 
Hashable BatchDetectKeyPhrasesItemResult Source # 
FromJSON BatchDetectKeyPhrasesItemResult Source # 
NFData BatchDetectKeyPhrasesItemResult Source # 
type Rep BatchDetectKeyPhrasesItemResult Source # 
type Rep BatchDetectKeyPhrasesItemResult = D1 * (MetaData "BatchDetectKeyPhrasesItemResult" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "BatchDetectKeyPhrasesItemResult'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdkpirIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_bdkpirKeyPhrases") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [KeyPhrase])))))

batchDetectKeyPhrasesItemResult :: BatchDetectKeyPhrasesItemResult Source #

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

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

bdkpirIndex :: Lens' BatchDetectKeyPhrasesItemResult (Maybe Int) Source #

The zero-based index of the document in the input list.

bdkpirKeyPhrases :: Lens' BatchDetectKeyPhrasesItemResult [KeyPhrase] Source #

One or more KeyPhrase objects, one for each key phrase detected in the document.

BatchDetectSentimentItemResult

data BatchDetectSentimentItemResult Source #

The result of calling the operation. The operation returns one object for each document that is successfully processed by the operation.

See: batchDetectSentimentItemResult smart constructor.

Instances

Eq BatchDetectSentimentItemResult Source # 
Data BatchDetectSentimentItemResult Source # 

Methods

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

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

toConstr :: BatchDetectSentimentItemResult -> Constr #

dataTypeOf :: BatchDetectSentimentItemResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BatchDetectSentimentItemResult Source # 
Show BatchDetectSentimentItemResult Source # 
Generic BatchDetectSentimentItemResult Source # 
Hashable BatchDetectSentimentItemResult Source # 
FromJSON BatchDetectSentimentItemResult Source # 
NFData BatchDetectSentimentItemResult Source # 
type Rep BatchDetectSentimentItemResult Source # 
type Rep BatchDetectSentimentItemResult = D1 * (MetaData "BatchDetectSentimentItemResult" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "BatchDetectSentimentItemResult'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdsirSentiment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SentimentType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdsirSentimentScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SentimentScore))) (S1 * (MetaSel (Just Symbol "_bdsirIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))))

batchDetectSentimentItemResult :: BatchDetectSentimentItemResult Source #

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

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

  • bdsirSentiment - The sentiment detected in the document.
  • bdsirSentimentScore - The level of confidence that Amazon Comprehend has in the accuracy of its sentiment detection.
  • bdsirIndex - The zero-based index of the document in the input list.

bdsirSentiment :: Lens' BatchDetectSentimentItemResult (Maybe SentimentType) Source #

The sentiment detected in the document.

bdsirSentimentScore :: Lens' BatchDetectSentimentItemResult (Maybe SentimentScore) Source #

The level of confidence that Amazon Comprehend has in the accuracy of its sentiment detection.

bdsirIndex :: Lens' BatchDetectSentimentItemResult (Maybe Int) Source #

The zero-based index of the document in the input list.

BatchItemError

data BatchItemError Source #

Describes an error that occurred while processing a document in a batch. The operation returns on BatchItemError object for each document that contained an error.

See: batchItemError smart constructor.

Instances

Eq BatchItemError Source # 
Data BatchItemError Source # 

Methods

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

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

toConstr :: BatchItemError -> Constr #

dataTypeOf :: BatchItemError -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BatchItemError Source # 
Show BatchItemError Source # 
Generic BatchItemError Source # 

Associated Types

type Rep BatchItemError :: * -> * #

Hashable BatchItemError Source # 
FromJSON BatchItemError Source # 
NFData BatchItemError Source # 

Methods

rnf :: BatchItemError -> () #

type Rep BatchItemError Source # 
type Rep BatchItemError = D1 * (MetaData "BatchItemError" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "BatchItemError'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bieErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bieErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_bieIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))))

batchItemError :: BatchItemError Source #

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

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

bieErrorCode :: Lens' BatchItemError (Maybe Text) Source #

The numeric error code of the error.

bieErrorMessage :: Lens' BatchItemError (Maybe Text) Source #

A text description of the error.

bieIndex :: Lens' BatchItemError (Maybe Int) Source #

The zero-based index of the document in the input list.

DominantLanguage

data DominantLanguage Source #

Returns the code for the dominant language in the input text and the level of confidence that Amazon Comprehend has in the accuracy of the detection.

See: dominantLanguage smart constructor.

Instances

Eq DominantLanguage Source # 
Data DominantLanguage Source # 

Methods

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

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

toConstr :: DominantLanguage -> Constr #

dataTypeOf :: DominantLanguage -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DominantLanguage Source # 
Show DominantLanguage Source # 
Generic DominantLanguage Source # 
Hashable DominantLanguage Source # 
FromJSON DominantLanguage Source # 
NFData DominantLanguage Source # 

Methods

rnf :: DominantLanguage -> () #

type Rep DominantLanguage Source # 
type Rep DominantLanguage = D1 * (MetaData "DominantLanguage" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "DominantLanguage'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_dlLanguageCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dlScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double)))))

dominantLanguage :: DominantLanguage Source #

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

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

  • dlLanguageCode - The RFC 5646 language code for the dominant language.
  • dlScore - The level of confidence that Amazon Comprehend has in the accuracy of the detection.

dlLanguageCode :: Lens' DominantLanguage (Maybe Text) Source #

The RFC 5646 language code for the dominant language.

dlScore :: Lens' DominantLanguage (Maybe Double) Source #

The level of confidence that Amazon Comprehend has in the accuracy of the detection.

Entity

data Entity Source #

Provides information about an entity.

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 #

Read Entity Source # 
Show Entity Source # 
Generic Entity Source # 

Associated Types

type Rep Entity :: * -> * #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

Hashable Entity Source # 

Methods

hashWithSalt :: Int -> Entity -> Int #

hash :: Entity -> Int #

FromJSON Entity Source # 
NFData Entity Source # 

Methods

rnf :: Entity -> () #

type Rep Entity Source # 
type Rep Entity = D1 * (MetaData "Entity" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "Entity'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_eBeginOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_eText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eEndOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_eType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe EntityType)))))))

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:

  • eBeginOffset - A character offset in the input text that shows where the entity begins (the first character is at position 0). The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.
  • eText - The text of the entity.
  • eScore - The level of confidence that Amazon Comprehend has in the accuracy of the detection.
  • eEndOffset - A character offset in the input text that shows where the entity ends. The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.
  • eType - The entity's type.

eBeginOffset :: Lens' Entity (Maybe Int) Source #

A character offset in the input text that shows where the entity begins (the first character is at position 0). The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.

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

The text of the entity.

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

The level of confidence that Amazon Comprehend has in the accuracy of the detection.

eEndOffset :: Lens' Entity (Maybe Int) Source #

A character offset in the input text that shows where the entity ends. The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.

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

The entity's type.

InputDataConfig

data InputDataConfig Source #

The input properties for a topic detection job.

See: inputDataConfig smart constructor.

Instances

Eq InputDataConfig Source # 
Data InputDataConfig Source # 

Methods

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

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

toConstr :: InputDataConfig -> Constr #

dataTypeOf :: InputDataConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InputDataConfig Source # 
Show InputDataConfig Source # 
Generic InputDataConfig Source # 
Hashable InputDataConfig Source # 
ToJSON InputDataConfig Source # 
FromJSON InputDataConfig Source # 
NFData InputDataConfig Source # 

Methods

rnf :: InputDataConfig -> () #

type Rep InputDataConfig Source # 
type Rep InputDataConfig = D1 * (MetaData "InputDataConfig" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "InputDataConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_idcInputFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InputFormat))) (S1 * (MetaSel (Just Symbol "_idcS3URI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

inputDataConfig Source #

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

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

  • idcInputFormat - Specifies how the text in an input file should be processed: * ONE_DOC_PER_FILE - Each file is considered a separate document. Use this option when you are processing large documents, such as newspaper articles or scientific papers. * ONE_DOC_PER_LINE - Each line in a file is considered a separate document. Use this option when you are processing many short documents, such as text messages.
  • idcS3URI - The Amazon S3 URI for the input data. The URI must be in same region as the API endpoint that you are calling. The URI can point to a single input file or it can provide the prefix for a collection of data files. For example, if you use the URI S3:/bucketNameprefix , if the prefix is a single file, Amazon Comprehend uses that file as input. If more than one file begins with the prefix, Amazon Comprehend uses all of them as input.

idcInputFormat :: Lens' InputDataConfig (Maybe InputFormat) Source #

Specifies how the text in an input file should be processed: * ONE_DOC_PER_FILE - Each file is considered a separate document. Use this option when you are processing large documents, such as newspaper articles or scientific papers. * ONE_DOC_PER_LINE - Each line in a file is considered a separate document. Use this option when you are processing many short documents, such as text messages.

idcS3URI :: Lens' InputDataConfig Text Source #

The Amazon S3 URI for the input data. The URI must be in same region as the API endpoint that you are calling. The URI can point to a single input file or it can provide the prefix for a collection of data files. For example, if you use the URI S3:/bucketNameprefix , if the prefix is a single file, Amazon Comprehend uses that file as input. If more than one file begins with the prefix, Amazon Comprehend uses all of them as input.

KeyPhrase

data KeyPhrase Source #

Describes a key noun phrase.

See: keyPhrase smart constructor.

Instances

Eq KeyPhrase Source # 
Data KeyPhrase Source # 

Methods

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

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

toConstr :: KeyPhrase -> Constr #

dataTypeOf :: KeyPhrase -> DataType #

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

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

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

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

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

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

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

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

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

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

Read KeyPhrase Source # 
Show KeyPhrase Source # 
Generic KeyPhrase Source # 

Associated Types

type Rep KeyPhrase :: * -> * #

Hashable KeyPhrase Source # 
FromJSON KeyPhrase Source # 
NFData KeyPhrase Source # 

Methods

rnf :: KeyPhrase -> () #

type Rep KeyPhrase Source # 
type Rep KeyPhrase = D1 * (MetaData "KeyPhrase" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "KeyPhrase'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_kpBeginOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_kpText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_kpScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_kpEndOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))))

keyPhrase :: KeyPhrase Source #

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

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

  • kpBeginOffset - A character offset in the input text that shows where the key phrase begins (the first character is at position 0). The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.
  • kpText - The text of a key noun phrase.
  • kpScore - The level of confidence that Amazon Comprehend has in the accuracy of the detection.
  • kpEndOffset - A character offset in the input text where the key phrase ends. The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.

kpBeginOffset :: Lens' KeyPhrase (Maybe Int) Source #

A character offset in the input text that shows where the key phrase begins (the first character is at position 0). The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.

kpText :: Lens' KeyPhrase (Maybe Text) Source #

The text of a key noun phrase.

kpScore :: Lens' KeyPhrase (Maybe Double) Source #

The level of confidence that Amazon Comprehend has in the accuracy of the detection.

kpEndOffset :: Lens' KeyPhrase (Maybe Int) Source #

A character offset in the input text where the key phrase ends. The offset returns the position of each UTF-8 code point in the string. A code point is the abstract character from a particular graphical representation. For example, a multi-byte UTF-8 character maps to a single code point.

OutputDataConfig

data OutputDataConfig Source #

Provides configuration parameters for the output of topic detection jobs.

See: outputDataConfig smart constructor.

Instances

Eq OutputDataConfig Source # 
Data OutputDataConfig Source # 

Methods

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

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

toConstr :: OutputDataConfig -> Constr #

dataTypeOf :: OutputDataConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OutputDataConfig Source # 
Show OutputDataConfig Source # 
Generic OutputDataConfig Source # 
Hashable OutputDataConfig Source # 
ToJSON OutputDataConfig Source # 
FromJSON OutputDataConfig Source # 
NFData OutputDataConfig Source # 

Methods

rnf :: OutputDataConfig -> () #

type Rep OutputDataConfig Source # 
type Rep OutputDataConfig = D1 * (MetaData "OutputDataConfig" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" True) (C1 * (MetaCons "OutputDataConfig'" PrefixI True) (S1 * (MetaSel (Just Symbol "_odcS3URI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

outputDataConfig Source #

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

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

  • odcS3URI - The Amazon S3 URI where you want to write the output data. The URI must be in the same region as the API endpoint that you are calling. The service creates an output file called output.tar.gz . It is a compressed archive that contains two files, topic-terms.csv that lists the terms associated with each topic, and doc-topics.csv that lists the documents associated with each topic. For more information, see 'topic-modeling' .

odcS3URI :: Lens' OutputDataConfig Text Source #

The Amazon S3 URI where you want to write the output data. The URI must be in the same region as the API endpoint that you are calling. The service creates an output file called output.tar.gz . It is a compressed archive that contains two files, topic-terms.csv that lists the terms associated with each topic, and doc-topics.csv that lists the documents associated with each topic. For more information, see 'topic-modeling' .

SentimentScore

data SentimentScore Source #

Describes the level of confidence that Amazon Comprehend has in the accuracy of its detection of sentiments.

See: sentimentScore smart constructor.

Instances

Eq SentimentScore Source # 
Data SentimentScore Source # 

Methods

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

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

toConstr :: SentimentScore -> Constr #

dataTypeOf :: SentimentScore -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SentimentScore Source # 
Show SentimentScore Source # 
Generic SentimentScore Source # 

Associated Types

type Rep SentimentScore :: * -> * #

Hashable SentimentScore Source # 
FromJSON SentimentScore Source # 
NFData SentimentScore Source # 

Methods

rnf :: SentimentScore -> () #

type Rep SentimentScore Source # 
type Rep SentimentScore = D1 * (MetaData "SentimentScore" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "SentimentScore'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ssMixed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_ssNegative") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ssNeutral") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_ssPositive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))))))

sentimentScore :: SentimentScore Source #

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

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

  • ssMixed - The level of confidence that Amazon Comprehend has in the accuracy of its detection of the MIXED sentiment.
  • ssNegative - The level of confidence that Amazon Comprehend has in the accuracy of its detection of the NEGATIVE sentiment.
  • ssNeutral - The level of confidence that Amazon Comprehend has in the accuracy of its detection of the NEUTRAL sentiment.
  • ssPositive - The level of confidence that Amazon Comprehend has in the accuracy of its detection of the POSITIVE sentiment.

ssMixed :: Lens' SentimentScore (Maybe Double) Source #

The level of confidence that Amazon Comprehend has in the accuracy of its detection of the MIXED sentiment.

ssNegative :: Lens' SentimentScore (Maybe Double) Source #

The level of confidence that Amazon Comprehend has in the accuracy of its detection of the NEGATIVE sentiment.

ssNeutral :: Lens' SentimentScore (Maybe Double) Source #

The level of confidence that Amazon Comprehend has in the accuracy of its detection of the NEUTRAL sentiment.

ssPositive :: Lens' SentimentScore (Maybe Double) Source #

The level of confidence that Amazon Comprehend has in the accuracy of its detection of the POSITIVE sentiment.

TopicsDetectionJobFilter

data TopicsDetectionJobFilter Source #

Provides information for filtering topic detection jobs. For more information, see .

See: topicsDetectionJobFilter smart constructor.

Instances

Eq TopicsDetectionJobFilter Source # 
Data TopicsDetectionJobFilter Source # 

Methods

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

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

toConstr :: TopicsDetectionJobFilter -> Constr #

dataTypeOf :: TopicsDetectionJobFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TopicsDetectionJobFilter Source # 
Show TopicsDetectionJobFilter Source # 
Generic TopicsDetectionJobFilter Source # 
Hashable TopicsDetectionJobFilter Source # 
ToJSON TopicsDetectionJobFilter Source # 
NFData TopicsDetectionJobFilter Source # 
type Rep TopicsDetectionJobFilter Source # 
type Rep TopicsDetectionJobFilter = D1 * (MetaData "TopicsDetectionJobFilter" "Network.AWS.Comprehend.Types.Product" "amazonka-comprehend-1.6.0-7ky9kDszQAoCEHl21SoVpv" False) (C1 * (MetaCons "TopicsDetectionJobFilter'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tdjfSubmitTimeAfter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_tdjfSubmitTimeBefore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tdjfJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tdjfJobStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe JobStatus))))))

topicsDetectionJobFilter :: TopicsDetectionJobFilter Source #

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

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

  • tdjfSubmitTimeAfter - Filters the list of jobs based on the time that the job was submitted for processing. Only returns jobs submitted after the specified time. Jobs are returned in ascending order, oldest to newest.
  • tdjfSubmitTimeBefore - Filters the list of jobs based on the time that the job was submitted for processing. Only returns jobs submitted before the specified time. Jobs are returned in descending order, newest to oldest.
  • tdjfJobName -
  • tdjfJobStatus - Filters the list of topic detection jobs based on job status. Returns only jobs with the specified status.

tdjfSubmitTimeAfter :: Lens' TopicsDetectionJobFilter (Maybe UTCTime) Source #

Filters the list of jobs based on the time that the job was submitted for processing. Only returns jobs submitted after the specified time. Jobs are returned in ascending order, oldest to newest.

tdjfSubmitTimeBefore :: Lens' TopicsDetectionJobFilter (Maybe UTCTime) Source #

Filters the list of jobs based on the time that the job was submitted for processing. Only returns jobs submitted before the specified time. Jobs are returned in descending order, newest to oldest.

tdjfJobStatus :: Lens' TopicsDetectionJobFilter (Maybe JobStatus) Source #

Filters the list of topic detection jobs based on job status. Returns only jobs with the specified status.

TopicsDetectionJobProperties

data TopicsDetectionJobProperties Source #

Provides information about a topic detection job.

See: topicsDetectionJobProperties smart constructor.

Instances

Eq TopicsDetectionJobProperties Source # 
Data TopicsDetectionJobProperties Source # 

Methods

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

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

toConstr :: TopicsDetectionJobProperties -> Constr #

dataTypeOf :: TopicsDetectionJobProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TopicsDetectionJobProperties Source # 
Show TopicsDetectionJobProperties Source # 
Generic TopicsDetectionJobProperties Source # 
Hashable TopicsDetectionJobProperties Source # 
FromJSON TopicsDetectionJobProperties Source # 
NFData TopicsDetectionJobProperties Source # 
type Rep TopicsDetectionJobProperties Source # 

topicsDetectionJobProperties :: TopicsDetectionJobProperties Source #

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

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

  • tdjpJobId - The identifier assigned to the topic detection job.
  • tdjpJobName - The name of the topic detection job.
  • tdjpInputDataConfig - The input data configuration supplied when you created the topic detection job.
  • tdjpEndTime - The time that the topic detection job was completed.
  • tdjpOutputDataConfig - The output data configuration supplied when you created the topic detection job.
  • tdjpNumberOfTopics - The number of topics to detect supplied when you created the topic detection job. The default is 10.
  • tdjpJobStatus - The current status of the topic detection job. If the status is Failed , the reason for the failure is shown in the Message field.
  • tdjpMessage - A description for the status of a job.
  • tdjpSubmitTime - The time that the topic detection job was submitted for processing.

tdjpJobId :: Lens' TopicsDetectionJobProperties (Maybe Text) Source #

The identifier assigned to the topic detection job.

tdjpJobName :: Lens' TopicsDetectionJobProperties (Maybe Text) Source #

The name of the topic detection job.

tdjpInputDataConfig :: Lens' TopicsDetectionJobProperties (Maybe InputDataConfig) Source #

The input data configuration supplied when you created the topic detection job.

tdjpEndTime :: Lens' TopicsDetectionJobProperties (Maybe UTCTime) Source #

The time that the topic detection job was completed.

tdjpOutputDataConfig :: Lens' TopicsDetectionJobProperties (Maybe OutputDataConfig) Source #

The output data configuration supplied when you created the topic detection job.

tdjpNumberOfTopics :: Lens' TopicsDetectionJobProperties (Maybe Int) Source #

The number of topics to detect supplied when you created the topic detection job. The default is 10.

tdjpJobStatus :: Lens' TopicsDetectionJobProperties (Maybe JobStatus) Source #

The current status of the topic detection job. If the status is Failed , the reason for the failure is shown in the Message field.

tdjpMessage :: Lens' TopicsDetectionJobProperties (Maybe Text) Source #

A description for the status of a job.

tdjpSubmitTime :: Lens' TopicsDetectionJobProperties (Maybe UTCTime) Source #

The time that the topic detection job was submitted for processing.