amazonka-cloudsearch-1.6.0: Amazon CloudSearch 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.CloudSearch.Types

Contents

Description

 

Synopsis

Service Configuration

cloudSearch :: Service Source #

API version 2013-01-01 of the Amazon CloudSearch SDK configuration.

Errors

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

An error occurred while processing the request.

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

The request was rejected because it attempted an operation which is not enabled.

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

An internal error occurred while processing the request. If this problem persists, report an issue from the Service Health Dashboard .

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

The request was rejected because it specified an invalid type definition.

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

The request was rejected because it attempted to reference a resource that does not exist.

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

The request was rejected because a resource limit has already been met.

AlgorithmicStemming

data AlgorithmicStemming Source #

Constructors

ASFull 
ASLight 
ASMinimal 
ASNone 

Instances

Bounded AlgorithmicStemming Source # 
Enum AlgorithmicStemming Source # 
Eq AlgorithmicStemming Source # 
Data AlgorithmicStemming Source # 

Methods

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

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

toConstr :: AlgorithmicStemming -> Constr #

dataTypeOf :: AlgorithmicStemming -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AlgorithmicStemming Source # 
Read AlgorithmicStemming Source # 
Show AlgorithmicStemming Source # 
Generic AlgorithmicStemming Source # 
Hashable AlgorithmicStemming Source # 
NFData AlgorithmicStemming Source # 

Methods

rnf :: AlgorithmicStemming -> () #

FromXML AlgorithmicStemming Source # 
ToHeader AlgorithmicStemming Source # 
ToQuery AlgorithmicStemming Source # 
ToByteString AlgorithmicStemming Source # 
FromText AlgorithmicStemming Source # 
ToText AlgorithmicStemming Source # 
type Rep AlgorithmicStemming Source # 
type Rep AlgorithmicStemming = D1 * (MetaData "AlgorithmicStemming" "Network.AWS.CloudSearch.Types.Sum" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ASFull" PrefixI False) (U1 *)) (C1 * (MetaCons "ASLight" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ASMinimal" PrefixI False) (U1 *)) (C1 * (MetaCons "ASNone" PrefixI False) (U1 *))))

AnalysisSchemeLanguage

data AnalysisSchemeLanguage Source #

An IETF RFC 4646 language code or mul for multiple languages.

Constructors

AR 
BG 
CA 
CS 
DA 
DE 
EL 
EN 
ES 
EU 
FA 
FI 
FR 
GA 
GL 
HE 
HI 
HU 
HY 
IT 
Id 
JA 
KO 
LV 
Mul 
NL 
NO 
PT 
RO 
RU 
SV 
TH 
TR 
ZhHans 
ZhHant 

Instances

Bounded AnalysisSchemeLanguage Source # 
Enum AnalysisSchemeLanguage Source # 
Eq AnalysisSchemeLanguage Source # 
Data AnalysisSchemeLanguage Source # 

Methods

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

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

toConstr :: AnalysisSchemeLanguage -> Constr #

dataTypeOf :: AnalysisSchemeLanguage -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnalysisSchemeLanguage Source # 
Read AnalysisSchemeLanguage Source # 
Show AnalysisSchemeLanguage Source # 
Generic AnalysisSchemeLanguage Source # 
Hashable AnalysisSchemeLanguage Source # 
NFData AnalysisSchemeLanguage Source # 

Methods

rnf :: AnalysisSchemeLanguage -> () #

FromXML AnalysisSchemeLanguage Source # 
ToHeader AnalysisSchemeLanguage Source # 
ToQuery AnalysisSchemeLanguage Source # 
ToByteString AnalysisSchemeLanguage Source # 
FromText AnalysisSchemeLanguage Source # 
ToText AnalysisSchemeLanguage Source # 
type Rep AnalysisSchemeLanguage Source # 
type Rep AnalysisSchemeLanguage = D1 * (MetaData "AnalysisSchemeLanguage" "Network.AWS.CloudSearch.Types.Sum" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "AR" PrefixI False) (U1 *)) (C1 * (MetaCons "BG" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CA" PrefixI False) (U1 *)) (C1 * (MetaCons "CS" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "DA" PrefixI False) (U1 *)) (C1 * (MetaCons "DE" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EL" PrefixI False) (U1 *)) (C1 * (MetaCons "EN" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ES" PrefixI False) (U1 *)) (C1 * (MetaCons "EU" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FA" PrefixI False) (U1 *)) (C1 * (MetaCons "FI" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "FR" PrefixI False) (U1 *)) (C1 * (MetaCons "GA" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "GL" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "HE" PrefixI False) (U1 *)) (C1 * (MetaCons "HI" PrefixI False) (U1 *))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "HU" PrefixI False) (U1 *)) (C1 * (MetaCons "HY" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "IT" PrefixI False) (U1 *)) (C1 * (MetaCons "Id" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "JA" PrefixI False) (U1 *)) (C1 * (MetaCons "KO" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LV" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Mul" PrefixI False) (U1 *)) (C1 * (MetaCons "NL" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NO" PrefixI False) (U1 *)) (C1 * (MetaCons "PT" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "RO" PrefixI False) (U1 *)) (C1 * (MetaCons "RU" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "SV" PrefixI False) (U1 *)) (C1 * (MetaCons "TH" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TR" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ZhHans" PrefixI False) (U1 *)) (C1 * (MetaCons "ZhHant" PrefixI False) (U1 *))))))))

IndexFieldType

data IndexFieldType Source #

The type of field. The valid options for a field depend on the field type. For more information about the supported field types, see Configuring Index Fields in the Amazon CloudSearch Developer Guide .

Instances

Bounded IndexFieldType Source # 
Enum IndexFieldType Source # 
Eq IndexFieldType Source # 
Data IndexFieldType Source # 

Methods

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

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

toConstr :: IndexFieldType -> Constr #

dataTypeOf :: IndexFieldType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IndexFieldType Source # 
Read IndexFieldType Source # 
Show IndexFieldType Source # 
Generic IndexFieldType Source # 

Associated Types

type Rep IndexFieldType :: * -> * #

Hashable IndexFieldType Source # 
NFData IndexFieldType Source # 

Methods

rnf :: IndexFieldType -> () #

FromXML IndexFieldType Source # 
ToHeader IndexFieldType Source # 
ToQuery IndexFieldType Source # 
ToByteString IndexFieldType Source # 
FromText IndexFieldType Source # 
ToText IndexFieldType Source # 
type Rep IndexFieldType Source # 
type Rep IndexFieldType = D1 * (MetaData "IndexFieldType" "Network.AWS.CloudSearch.Types.Sum" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Date" PrefixI False) (U1 *)) (C1 * (MetaCons "DateArray" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Double" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DoubleArray" PrefixI False) (U1 *)) (C1 * (MetaCons "Int" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "IntArray" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Latlon" PrefixI False) (U1 *)) (C1 * (MetaCons "Literal" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "LiteralArray" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Text" PrefixI False) (U1 *)) (C1 * (MetaCons "TextArray" PrefixI False) (U1 *))))))

OptionState

data OptionState Source #

The state of processing a change to an option. One of:

  • RequiresIndexDocuments: The option's latest value will not be deployed until IndexDocuments has been called and indexing is complete. * Processing: The option's latest value is in the process of being activated. * Active: The option's latest value is fully deployed. * FailedToValidate: The option value is not compatible with the domain's data and cannot be used to index the data. You must either modify the option value or update or remove the incompatible documents.

Instances

Bounded OptionState Source # 
Enum OptionState Source # 
Eq OptionState Source # 
Data OptionState Source # 

Methods

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

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

toConstr :: OptionState -> Constr #

dataTypeOf :: OptionState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OptionState Source # 
Read OptionState Source # 
Show OptionState Source # 
Generic OptionState Source # 

Associated Types

type Rep OptionState :: * -> * #

Hashable OptionState Source # 
NFData OptionState Source # 

Methods

rnf :: OptionState -> () #

FromXML OptionState Source # 
ToHeader OptionState Source # 
ToQuery OptionState Source # 
ToByteString OptionState Source # 
FromText OptionState Source # 
ToText OptionState Source # 

Methods

toText :: OptionState -> Text #

type Rep OptionState Source # 
type Rep OptionState = D1 * (MetaData "OptionState" "Network.AWS.CloudSearch.Types.Sum" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Active" PrefixI False) (U1 *)) (C1 * (MetaCons "FailedToValidate" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Processing" PrefixI False) (U1 *)) (C1 * (MetaCons "RequiresIndexDocuments" PrefixI False) (U1 *))))

PartitionInstanceType

data PartitionInstanceType Source #

The instance type (such as search.m1.small ) on which an index partition is hosted.

Instances

Bounded PartitionInstanceType Source # 
Enum PartitionInstanceType Source # 
Eq PartitionInstanceType Source # 
Data PartitionInstanceType Source # 

Methods

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

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

toConstr :: PartitionInstanceType -> Constr #

dataTypeOf :: PartitionInstanceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PartitionInstanceType Source # 
Read PartitionInstanceType Source # 
Show PartitionInstanceType Source # 
Generic PartitionInstanceType Source # 
Hashable PartitionInstanceType Source # 
NFData PartitionInstanceType Source # 

Methods

rnf :: PartitionInstanceType -> () #

FromXML PartitionInstanceType Source # 
ToHeader PartitionInstanceType Source # 
ToQuery PartitionInstanceType Source # 
ToByteString PartitionInstanceType Source # 
FromText PartitionInstanceType Source # 
ToText PartitionInstanceType Source # 
type Rep PartitionInstanceType Source # 
type Rep PartitionInstanceType = D1 * (MetaData "PartitionInstanceType" "Network.AWS.CloudSearch.Types.Sum" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Search_M1_Large" PrefixI False) (U1 *)) (C1 * (MetaCons "Search_M1_Small" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Search_M2_2XLarge" PrefixI False) (U1 *)) (C1 * (MetaCons "Search_M2_XLarge" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Search_M3_2XLarge" PrefixI False) (U1 *)) (C1 * (MetaCons "Search_M3_Large" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Search_M3_Medium" PrefixI False) (U1 *)) (C1 * (MetaCons "Search_M3_XLarge" PrefixI False) (U1 *)))))

SuggesterFuzzyMatching

data SuggesterFuzzyMatching Source #

Constructors

High 
Low 
None 

Instances

Bounded SuggesterFuzzyMatching Source # 
Enum SuggesterFuzzyMatching Source # 
Eq SuggesterFuzzyMatching Source # 
Data SuggesterFuzzyMatching Source # 

Methods

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

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

toConstr :: SuggesterFuzzyMatching -> Constr #

dataTypeOf :: SuggesterFuzzyMatching -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SuggesterFuzzyMatching Source # 
Read SuggesterFuzzyMatching Source # 
Show SuggesterFuzzyMatching Source # 
Generic SuggesterFuzzyMatching Source # 
Hashable SuggesterFuzzyMatching Source # 
NFData SuggesterFuzzyMatching Source # 

Methods

rnf :: SuggesterFuzzyMatching -> () #

FromXML SuggesterFuzzyMatching Source # 
ToHeader SuggesterFuzzyMatching Source # 
ToQuery SuggesterFuzzyMatching Source # 
ToByteString SuggesterFuzzyMatching Source # 
FromText SuggesterFuzzyMatching Source # 
ToText SuggesterFuzzyMatching Source # 
type Rep SuggesterFuzzyMatching Source # 
type Rep SuggesterFuzzyMatching = D1 * (MetaData "SuggesterFuzzyMatching" "Network.AWS.CloudSearch.Types.Sum" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) ((:+:) * (C1 * (MetaCons "High" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Low" PrefixI False) (U1 *)) (C1 * (MetaCons "None" PrefixI False) (U1 *))))

AccessPoliciesStatus

data AccessPoliciesStatus Source #

The configured access rules for the domain's document and search endpoints, and the current status of those rules.

See: accessPoliciesStatus smart constructor.

Instances

Eq AccessPoliciesStatus Source # 
Data AccessPoliciesStatus Source # 

Methods

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

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

toConstr :: AccessPoliciesStatus -> Constr #

dataTypeOf :: AccessPoliciesStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AccessPoliciesStatus Source # 
Show AccessPoliciesStatus Source # 
Generic AccessPoliciesStatus Source # 
Hashable AccessPoliciesStatus Source # 
NFData AccessPoliciesStatus Source # 

Methods

rnf :: AccessPoliciesStatus -> () #

FromXML AccessPoliciesStatus Source # 
type Rep AccessPoliciesStatus Source # 
type Rep AccessPoliciesStatus = D1 * (MetaData "AccessPoliciesStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "AccessPoliciesStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_apsOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_apsStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionStatus))))

accessPoliciesStatus Source #

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

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

AnalysisOptions

data AnalysisOptions Source #

Synonyms, stopwords, and stemming options for an analysis scheme. Includes tokenization dictionary for Japanese.

See: analysisOptions smart constructor.

Instances

Eq AnalysisOptions Source # 
Data AnalysisOptions Source # 

Methods

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

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

toConstr :: AnalysisOptions -> Constr #

dataTypeOf :: AnalysisOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalysisOptions Source # 
Show AnalysisOptions Source # 
Generic AnalysisOptions Source # 
Hashable AnalysisOptions Source # 
NFData AnalysisOptions Source # 

Methods

rnf :: AnalysisOptions -> () #

FromXML AnalysisOptions Source # 
ToQuery AnalysisOptions Source # 
type Rep AnalysisOptions Source # 
type Rep AnalysisOptions = D1 * (MetaData "AnalysisOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "AnalysisOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_aoAlgorithmicStemming") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AlgorithmicStemming))) (S1 * (MetaSel (Just Symbol "_aoStopwords") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aoJapaneseTokenizationDictionary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aoSynonyms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_aoStemmingDictionary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

analysisOptions :: AnalysisOptions Source #

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

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

  • aoAlgorithmicStemming - The level of algorithmic stemming to perform: none , minimal , light , or full . The available levels vary depending on the language. For more information, see Language Specific Text Processing Settings in the Amazon CloudSearch Developer Guide
  • aoStopwords - A JSON array of terms to ignore during indexing and searching. For example, ["a", "an", "the", "of"] . The stopwords dictionary must explicitly list each word you want to ignore. Wildcards and regular expressions are not supported.
  • aoJapaneseTokenizationDictionary - A JSON array that contains a collection of terms, tokens, readings and part of speech for Japanese Tokenizaiton. The Japanese tokenization dictionary enables you to override the default tokenization for selected terms. This is only valid for Japanese language fields.
  • aoSynonyms - A JSON object that defines synonym groups and aliases. A synonym group is an array of arrays, where each sub-array is a group of terms where each term in the group is considered a synonym of every other term in the group. The aliases value is an object that contains a collection of string:value pairs where the string specifies a term and the array of values specifies each of the aliases for that term. An alias is considered a synonym of the specified term, but the term is not considered a synonym of the alias. For more information about specifying synonyms, see Synonyms in the Amazon CloudSearch Developer Guide .
  • aoStemmingDictionary - A JSON object that contains a collection of string:value pairs that each map a term to its stem. For example, {"term1": "stem1", "term2": "stem2", "term3": "stem3"} . The stemming dictionary is applied in addition to any algorithmic stemming. This enables you to override the results of the algorithmic stemming to correct specific cases of overstemming or understemming. The maximum size of a stemming dictionary is 500 KB.

aoAlgorithmicStemming :: Lens' AnalysisOptions (Maybe AlgorithmicStemming) Source #

The level of algorithmic stemming to perform: none , minimal , light , or full . The available levels vary depending on the language. For more information, see Language Specific Text Processing Settings in the Amazon CloudSearch Developer Guide

aoStopwords :: Lens' AnalysisOptions (Maybe Text) Source #

A JSON array of terms to ignore during indexing and searching. For example, ["a", "an", "the", "of"] . The stopwords dictionary must explicitly list each word you want to ignore. Wildcards and regular expressions are not supported.

aoJapaneseTokenizationDictionary :: Lens' AnalysisOptions (Maybe Text) Source #

A JSON array that contains a collection of terms, tokens, readings and part of speech for Japanese Tokenizaiton. The Japanese tokenization dictionary enables you to override the default tokenization for selected terms. This is only valid for Japanese language fields.

aoSynonyms :: Lens' AnalysisOptions (Maybe Text) Source #

A JSON object that defines synonym groups and aliases. A synonym group is an array of arrays, where each sub-array is a group of terms where each term in the group is considered a synonym of every other term in the group. The aliases value is an object that contains a collection of string:value pairs where the string specifies a term and the array of values specifies each of the aliases for that term. An alias is considered a synonym of the specified term, but the term is not considered a synonym of the alias. For more information about specifying synonyms, see Synonyms in the Amazon CloudSearch Developer Guide .

aoStemmingDictionary :: Lens' AnalysisOptions (Maybe Text) Source #

A JSON object that contains a collection of string:value pairs that each map a term to its stem. For example, {"term1": "stem1", "term2": "stem2", "term3": "stem3"} . The stemming dictionary is applied in addition to any algorithmic stemming. This enables you to override the results of the algorithmic stemming to correct specific cases of overstemming or understemming. The maximum size of a stemming dictionary is 500 KB.

AnalysisScheme

data AnalysisScheme Source #

Configuration information for an analysis scheme. Each analysis scheme has a unique name and specifies the language of the text to be processed. The following options can be configured for an analysis scheme: Synonyms , Stopwords , StemmingDictionary , JapaneseTokenizationDictionary and AlgorithmicStemming .

See: analysisScheme smart constructor.

Instances

Eq AnalysisScheme Source # 
Data AnalysisScheme Source # 

Methods

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

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

toConstr :: AnalysisScheme -> Constr #

dataTypeOf :: AnalysisScheme -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalysisScheme Source # 
Show AnalysisScheme Source # 
Generic AnalysisScheme Source # 

Associated Types

type Rep AnalysisScheme :: * -> * #

Hashable AnalysisScheme Source # 
NFData AnalysisScheme Source # 

Methods

rnf :: AnalysisScheme -> () #

FromXML AnalysisScheme Source # 
ToQuery AnalysisScheme Source # 
type Rep AnalysisScheme Source # 
type Rep AnalysisScheme = D1 * (MetaData "AnalysisScheme" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "AnalysisScheme'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_asAnalysisOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AnalysisOptions))) ((:*:) * (S1 * (MetaSel (Just Symbol "_asAnalysisSchemeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_asAnalysisSchemeLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * AnalysisSchemeLanguage)))))

analysisScheme Source #

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

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

AnalysisSchemeStatus

data AnalysisSchemeStatus Source #

The status and configuration of an AnalysisScheme .

See: analysisSchemeStatus smart constructor.

Instances

Eq AnalysisSchemeStatus Source # 
Data AnalysisSchemeStatus Source # 

Methods

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

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

toConstr :: AnalysisSchemeStatus -> Constr #

dataTypeOf :: AnalysisSchemeStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnalysisSchemeStatus Source # 
Show AnalysisSchemeStatus Source # 
Generic AnalysisSchemeStatus Source # 
Hashable AnalysisSchemeStatus Source # 
NFData AnalysisSchemeStatus Source # 

Methods

rnf :: AnalysisSchemeStatus -> () #

FromXML AnalysisSchemeStatus Source # 
type Rep AnalysisSchemeStatus Source # 
type Rep AnalysisSchemeStatus = D1 * (MetaData "AnalysisSchemeStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "AnalysisSchemeStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_assOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * AnalysisScheme)) (S1 * (MetaSel (Just Symbol "_assStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionStatus))))

analysisSchemeStatus Source #

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

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

AvailabilityOptionsStatus

data AvailabilityOptionsStatus Source #

The status and configuration of the domain's availability options.

See: availabilityOptionsStatus smart constructor.

Instances

Eq AvailabilityOptionsStatus Source # 
Data AvailabilityOptionsStatus Source # 

Methods

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

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

toConstr :: AvailabilityOptionsStatus -> Constr #

dataTypeOf :: AvailabilityOptionsStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AvailabilityOptionsStatus Source # 
Show AvailabilityOptionsStatus Source # 
Generic AvailabilityOptionsStatus Source # 
Hashable AvailabilityOptionsStatus Source # 
NFData AvailabilityOptionsStatus Source # 
FromXML AvailabilityOptionsStatus Source # 
type Rep AvailabilityOptionsStatus Source # 
type Rep AvailabilityOptionsStatus = D1 * (MetaData "AvailabilityOptionsStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "AvailabilityOptionsStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_aosOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "_aosStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionStatus))))

availabilityOptionsStatus Source #

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

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

  • aosOptions - The availability options configured for the domain.
  • aosStatus - Undocumented member.

aosOptions :: Lens' AvailabilityOptionsStatus Bool Source #

The availability options configured for the domain.

DateArrayOptions

data DateArrayOptions Source #

Options for a field that contains an array of dates. Present if IndexFieldType specifies the field is of type date-array . All options are enabled by default.

See: dateArrayOptions smart constructor.

Instances

Eq DateArrayOptions Source # 
Data DateArrayOptions Source # 

Methods

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

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

toConstr :: DateArrayOptions -> Constr #

dataTypeOf :: DateArrayOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DateArrayOptions Source # 
Show DateArrayOptions Source # 
Generic DateArrayOptions Source # 
Hashable DateArrayOptions Source # 
NFData DateArrayOptions Source # 

Methods

rnf :: DateArrayOptions -> () #

FromXML DateArrayOptions Source # 
ToQuery DateArrayOptions Source # 
type Rep DateArrayOptions Source # 
type Rep DateArrayOptions = D1 * (MetaData "DateArrayOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "DateArrayOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_daosSourceFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_daosReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_daosFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_daosSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_daosDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

dateArrayOptions :: DateArrayOptions Source #

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

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

daosSourceFields :: Lens' DateArrayOptions (Maybe Text) Source #

A list of source fields to map to the field.

daosReturnEnabled :: Lens' DateArrayOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

daosFacetEnabled :: Lens' DateArrayOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

daosSearchEnabled :: Lens' DateArrayOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

daosDefaultValue :: Lens' DateArrayOptions (Maybe Text) Source #

A value to use for the field if the field isn't specified for a document.

DateOptions

data DateOptions Source #

Options for a date field. Dates and times are specified in UTC (Coordinated Universal Time) according to IETF RFC3339: yyyy-mm-ddT00:00:00Z. Present if IndexFieldType specifies the field is of type date . All options are enabled by default.

See: dateOptions smart constructor.

Instances

Eq DateOptions Source # 
Data DateOptions Source # 

Methods

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

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

toConstr :: DateOptions -> Constr #

dataTypeOf :: DateOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DateOptions Source # 
Show DateOptions Source # 
Generic DateOptions Source # 

Associated Types

type Rep DateOptions :: * -> * #

Hashable DateOptions Source # 
NFData DateOptions Source # 

Methods

rnf :: DateOptions -> () #

FromXML DateOptions Source # 
ToQuery DateOptions Source # 
type Rep DateOptions Source # 
type Rep DateOptions = D1 * (MetaData "DateOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "DateOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_doSourceField") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_doReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_doFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_doSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_doSortEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_doDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

dateOptions :: DateOptions Source #

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

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

  • doSourceField - Undocumented member.
  • doReturnEnabled - Whether the contents of the field can be returned in the search results.
  • doFacetEnabled - Whether facet information can be returned for the field.
  • doSearchEnabled - Whether the contents of the field are searchable.
  • doSortEnabled - Whether the field can be used to sort the search results.
  • doDefaultValue - A value to use for the field if the field isn't specified for a document.

doSourceField :: Lens' DateOptions (Maybe Text) Source #

Undocumented member.

doReturnEnabled :: Lens' DateOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

doFacetEnabled :: Lens' DateOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

doSearchEnabled :: Lens' DateOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

doSortEnabled :: Lens' DateOptions (Maybe Bool) Source #

Whether the field can be used to sort the search results.

doDefaultValue :: Lens' DateOptions (Maybe Text) Source #

A value to use for the field if the field isn't specified for a document.

DocumentSuggesterOptions

data DocumentSuggesterOptions Source #

Options for a search suggester.

See: documentSuggesterOptions smart constructor.

Instances

Eq DocumentSuggesterOptions Source # 
Data DocumentSuggesterOptions Source # 

Methods

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

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

toConstr :: DocumentSuggesterOptions -> Constr #

dataTypeOf :: DocumentSuggesterOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DocumentSuggesterOptions Source # 
Show DocumentSuggesterOptions Source # 
Generic DocumentSuggesterOptions Source # 
Hashable DocumentSuggesterOptions Source # 
NFData DocumentSuggesterOptions Source # 
FromXML DocumentSuggesterOptions Source # 
ToQuery DocumentSuggesterOptions Source # 
type Rep DocumentSuggesterOptions Source # 
type Rep DocumentSuggesterOptions = D1 * (MetaData "DocumentSuggesterOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "DocumentSuggesterOptions'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsoSortExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsoFuzzyMatching") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SuggesterFuzzyMatching))) (S1 * (MetaSel (Just Symbol "_dsoSourceField") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

documentSuggesterOptions Source #

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

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

  • dsoSortExpression - An expression that computes a score for each suggestion to control how they are sorted. The scores are rounded to the nearest integer, with a floor of 0 and a ceiling of 2^31-1. A document's relevance score is not computed for suggestions, so sort expressions cannot reference the _score value. To sort suggestions using a numeric field or existing expression, simply specify the name of the field or expression. If no expression is configured for the suggester, the suggestions are sorted with the closest matches listed first.
  • dsoFuzzyMatching - The level of fuzziness allowed when suggesting matches for a string: none , low , or high . With none, the specified string is treated as an exact prefix. With low, suggestions must differ from the specified string by no more than one character. With high, suggestions can differ by up to two characters. The default is none.
  • dsoSourceField - The name of the index field you want to use for suggestions.

dsoSortExpression :: Lens' DocumentSuggesterOptions (Maybe Text) Source #

An expression that computes a score for each suggestion to control how they are sorted. The scores are rounded to the nearest integer, with a floor of 0 and a ceiling of 2^31-1. A document's relevance score is not computed for suggestions, so sort expressions cannot reference the _score value. To sort suggestions using a numeric field or existing expression, simply specify the name of the field or expression. If no expression is configured for the suggester, the suggestions are sorted with the closest matches listed first.

dsoFuzzyMatching :: Lens' DocumentSuggesterOptions (Maybe SuggesterFuzzyMatching) Source #

The level of fuzziness allowed when suggesting matches for a string: none , low , or high . With none, the specified string is treated as an exact prefix. With low, suggestions must differ from the specified string by no more than one character. With high, suggestions can differ by up to two characters. The default is none.

dsoSourceField :: Lens' DocumentSuggesterOptions Text Source #

The name of the index field you want to use for suggestions.

DomainStatus

data DomainStatus Source #

The current status of the search domain.

See: domainStatus smart constructor.

Instances

Eq DomainStatus Source # 
Data DomainStatus Source # 

Methods

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

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

toConstr :: DomainStatus -> Constr #

dataTypeOf :: DomainStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DomainStatus Source # 
Show DomainStatus Source # 
Generic DomainStatus Source # 

Associated Types

type Rep DomainStatus :: * -> * #

Hashable DomainStatus Source # 
NFData DomainStatus Source # 

Methods

rnf :: DomainStatus -> () #

FromXML DomainStatus Source # 
type Rep DomainStatus Source # 
type Rep DomainStatus = D1 * (MetaData "DomainStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "DomainStatus'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dsSearchInstanceCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsSearchInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dsDocService") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ServiceEndpoint))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_dsSearchService") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ServiceEndpoint)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dsLimits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Limits))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsSearchPartitionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_dsDeleted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dsProcessing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_dsDomainId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsDomainName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_dsRequiresIndexDocuments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)))))))

domainStatus Source #

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

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

  • dsSearchInstanceCount - The number of search instances that are available to process search requests.
  • dsSearchInstanceType - The instance type that is being used to process search requests.
  • dsDocService - The service endpoint for updating documents in a search domain.
  • dsARN - Undocumented member.
  • dsCreated - True if the search domain is created. It can take several minutes to initialize a domain when CreateDomain is called. Newly created search domains are returned from DescribeDomains with a false value for Created until domain creation is complete.
  • dsSearchService - The service endpoint for requesting search results from a search domain.
  • dsLimits - Undocumented member.
  • dsSearchPartitionCount - The number of partitions across which the search index is spread.
  • dsDeleted - True if the search domain has been deleted. The system must clean up resources dedicated to the search domain when DeleteDomain is called. Newly deleted search domains are returned from DescribeDomains with a true value for IsDeleted for several minutes until resource cleanup is complete.
  • dsProcessing - True if processing is being done to activate the current domain configuration.
  • dsDomainId - Undocumented member.
  • dsDomainName - Undocumented member.
  • dsRequiresIndexDocuments - True if IndexDocuments needs to be called to activate the current domain configuration.

dsSearchInstanceCount :: Lens' DomainStatus (Maybe Natural) Source #

The number of search instances that are available to process search requests.

dsSearchInstanceType :: Lens' DomainStatus (Maybe Text) Source #

The instance type that is being used to process search requests.

dsDocService :: Lens' DomainStatus (Maybe ServiceEndpoint) Source #

The service endpoint for updating documents in a search domain.

dsARN :: Lens' DomainStatus (Maybe Text) Source #

Undocumented member.

dsCreated :: Lens' DomainStatus (Maybe Bool) Source #

True if the search domain is created. It can take several minutes to initialize a domain when CreateDomain is called. Newly created search domains are returned from DescribeDomains with a false value for Created until domain creation is complete.

dsSearchService :: Lens' DomainStatus (Maybe ServiceEndpoint) Source #

The service endpoint for requesting search results from a search domain.

dsLimits :: Lens' DomainStatus (Maybe Limits) Source #

Undocumented member.

dsSearchPartitionCount :: Lens' DomainStatus (Maybe Natural) Source #

The number of partitions across which the search index is spread.

dsDeleted :: Lens' DomainStatus (Maybe Bool) Source #

True if the search domain has been deleted. The system must clean up resources dedicated to the search domain when DeleteDomain is called. Newly deleted search domains are returned from DescribeDomains with a true value for IsDeleted for several minutes until resource cleanup is complete.

dsProcessing :: Lens' DomainStatus (Maybe Bool) Source #

True if processing is being done to activate the current domain configuration.

dsDomainId :: Lens' DomainStatus Text Source #

Undocumented member.

dsDomainName :: Lens' DomainStatus Text Source #

Undocumented member.

dsRequiresIndexDocuments :: Lens' DomainStatus Bool Source #

True if IndexDocuments needs to be called to activate the current domain configuration.

DoubleArrayOptions

data DoubleArrayOptions Source #

Options for a field that contains an array of double-precision 64-bit floating point values. Present if IndexFieldType specifies the field is of type double-array . All options are enabled by default.

See: doubleArrayOptions smart constructor.

Instances

Eq DoubleArrayOptions Source # 
Data DoubleArrayOptions Source # 

Methods

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

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

toConstr :: DoubleArrayOptions -> Constr #

dataTypeOf :: DoubleArrayOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DoubleArrayOptions Source # 
Show DoubleArrayOptions Source # 
Generic DoubleArrayOptions Source # 
Hashable DoubleArrayOptions Source # 
NFData DoubleArrayOptions Source # 

Methods

rnf :: DoubleArrayOptions -> () #

FromXML DoubleArrayOptions Source # 
ToQuery DoubleArrayOptions Source # 
type Rep DoubleArrayOptions Source # 
type Rep DoubleArrayOptions = D1 * (MetaData "DoubleArrayOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "DoubleArrayOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_daoSourceFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_daoReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_daoFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_daoSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_daoDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double)))))))

doubleArrayOptions :: DoubleArrayOptions Source #

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

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

  • daoSourceFields - A list of source fields to map to the field.
  • daoReturnEnabled - Whether the contents of the field can be returned in the search results.
  • daoFacetEnabled - Whether facet information can be returned for the field.
  • daoSearchEnabled - Whether the contents of the field are searchable.
  • daoDefaultValue - A value to use for the field if the field isn't specified for a document.

daoSourceFields :: Lens' DoubleArrayOptions (Maybe Text) Source #

A list of source fields to map to the field.

daoReturnEnabled :: Lens' DoubleArrayOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

daoFacetEnabled :: Lens' DoubleArrayOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

daoSearchEnabled :: Lens' DoubleArrayOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

daoDefaultValue :: Lens' DoubleArrayOptions (Maybe Double) Source #

A value to use for the field if the field isn't specified for a document.

DoubleOptions

data DoubleOptions Source #

Options for a double-precision 64-bit floating point field. Present if IndexFieldType specifies the field is of type double . All options are enabled by default.

See: doubleOptions smart constructor.

Instances

Eq DoubleOptions Source # 
Data DoubleOptions Source # 

Methods

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

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

toConstr :: DoubleOptions -> Constr #

dataTypeOf :: DoubleOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DoubleOptions Source # 
Show DoubleOptions Source # 
Generic DoubleOptions Source # 

Associated Types

type Rep DoubleOptions :: * -> * #

Hashable DoubleOptions Source # 
NFData DoubleOptions Source # 

Methods

rnf :: DoubleOptions -> () #

FromXML DoubleOptions Source # 
ToQuery DoubleOptions Source # 
type Rep DoubleOptions Source # 
type Rep DoubleOptions = D1 * (MetaData "DoubleOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "DoubleOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dSourceField") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_dFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dSortEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_dDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double)))))))

doubleOptions :: DoubleOptions Source #

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

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

  • dSourceField - The name of the source field to map to the field.
  • dReturnEnabled - Whether the contents of the field can be returned in the search results.
  • dFacetEnabled - Whether facet information can be returned for the field.
  • dSearchEnabled - Whether the contents of the field are searchable.
  • dSortEnabled - Whether the field can be used to sort the search results.
  • dDefaultValue - A value to use for the field if the field isn't specified for a document. This can be important if you are using the field in an expression and that field is not present in every document.

dSourceField :: Lens' DoubleOptions (Maybe Text) Source #

The name of the source field to map to the field.

dReturnEnabled :: Lens' DoubleOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

dFacetEnabled :: Lens' DoubleOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

dSearchEnabled :: Lens' DoubleOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

dSortEnabled :: Lens' DoubleOptions (Maybe Bool) Source #

Whether the field can be used to sort the search results.

dDefaultValue :: Lens' DoubleOptions (Maybe Double) Source #

A value to use for the field if the field isn't specified for a document. This can be important if you are using the field in an expression and that field is not present in every document.

Expression

data Expression Source #

A named expression that can be evaluated at search time. Can be used to sort the search results, define other expressions, or return computed information in the search results.

See: expression smart constructor.

Instances

Eq Expression Source # 
Data Expression Source # 

Methods

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

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

toConstr :: Expression -> Constr #

dataTypeOf :: Expression -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Expression Source # 
Show Expression Source # 
Generic Expression Source # 

Associated Types

type Rep Expression :: * -> * #

Hashable Expression Source # 
NFData Expression Source # 

Methods

rnf :: Expression -> () #

FromXML Expression Source # 
ToQuery Expression Source # 
type Rep Expression Source # 
type Rep Expression = D1 * (MetaData "Expression" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "Expression'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_eExpressionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_eExpressionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

expression Source #

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

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

eExpressionName :: Lens' Expression Text Source #

Undocumented member.

eExpressionValue :: Lens' Expression Text Source #

Undocumented member.

ExpressionStatus

data ExpressionStatus Source #

The value of an Expression and its current status.

See: expressionStatus smart constructor.

Instances

Eq ExpressionStatus Source # 
Data ExpressionStatus Source # 

Methods

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

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

toConstr :: ExpressionStatus -> Constr #

dataTypeOf :: ExpressionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ExpressionStatus Source # 
Show ExpressionStatus Source # 
Generic ExpressionStatus Source # 
Hashable ExpressionStatus Source # 
NFData ExpressionStatus Source # 

Methods

rnf :: ExpressionStatus -> () #

FromXML ExpressionStatus Source # 
type Rep ExpressionStatus Source # 
type Rep ExpressionStatus = D1 * (MetaData "ExpressionStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "ExpressionStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_esOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Expression)) (S1 * (MetaSel (Just Symbol "_esStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionStatus))))

expressionStatus Source #

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

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

  • esOptions - The expression that is evaluated for sorting while processing a search request.
  • esStatus - Undocumented member.

esOptions :: Lens' ExpressionStatus Expression Source #

The expression that is evaluated for sorting while processing a search request.

IndexField

data IndexField Source #

Configuration information for a field in the index, including its name, type, and options. The supported options depend on the IndexFieldType .

See: indexField smart constructor.

Instances

Eq IndexField Source # 
Data IndexField Source # 

Methods

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

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

toConstr :: IndexField -> Constr #

dataTypeOf :: IndexField -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IndexField Source # 
Show IndexField Source # 
Generic IndexField Source # 

Associated Types

type Rep IndexField :: * -> * #

Hashable IndexField Source # 
NFData IndexField Source # 

Methods

rnf :: IndexField -> () #

FromXML IndexField Source # 
ToQuery IndexField Source # 
type Rep IndexField Source # 
type Rep IndexField = D1 * (MetaData "IndexField" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "IndexField'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ifDoubleArrayOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DoubleArrayOptions))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifDateOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DateOptions))) (S1 * (MetaSel (Just Symbol "_ifTextArrayOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe TextArrayOptions))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifDoubleOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DoubleOptions))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifTextOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe TextOptions))) (S1 * (MetaSel (Just Symbol "_ifLatLonOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LatLonOptions)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ifLiteralArrayOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LiteralArrayOptions))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifIntArrayOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe IntArrayOptions))) (S1 * (MetaSel (Just Symbol "_ifDateArrayOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DateArrayOptions))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ifIntOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe IntOptions))) (S1 * (MetaSel (Just Symbol "_ifLiteralOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LiteralOptions)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifIndexFieldName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_ifIndexFieldType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * IndexFieldType)))))))

indexField Source #

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

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

  • ifDoubleArrayOptions - Undocumented member.
  • ifDateOptions - Undocumented member.
  • ifTextArrayOptions - Undocumented member.
  • ifDoubleOptions - Undocumented member.
  • ifTextOptions - Undocumented member.
  • ifLatLonOptions - Undocumented member.
  • ifLiteralArrayOptions - Undocumented member.
  • ifIntArrayOptions - Undocumented member.
  • ifDateArrayOptions - Undocumented member.
  • ifIntOptions - Undocumented member.
  • ifLiteralOptions - Undocumented member.
  • ifIndexFieldName - A string that represents the name of an index field. CloudSearch supports regular index fields as well as dynamic fields. A dynamic field's name defines a pattern that begins or ends with a wildcard. Any document fields that don't map to a regular index field but do match a dynamic field's pattern are configured with the dynamic field's indexing options. Regular field names begin with a letter and can contain the following characters: a-z (lowercase), 0-9, and _ (underscore). Dynamic field names must begin or end with a wildcard (*). The wildcard can also be the only character in a dynamic field name. Multiple wildcards, and wildcards embedded within a string are not supported. The name score is reserved and cannot be used as a field name. To reference a document's ID, you can use the name _id .
  • ifIndexFieldType - Undocumented member.

ifIndexFieldName :: Lens' IndexField Text Source #

A string that represents the name of an index field. CloudSearch supports regular index fields as well as dynamic fields. A dynamic field's name defines a pattern that begins or ends with a wildcard. Any document fields that don't map to a regular index field but do match a dynamic field's pattern are configured with the dynamic field's indexing options. Regular field names begin with a letter and can contain the following characters: a-z (lowercase), 0-9, and _ (underscore). Dynamic field names must begin or end with a wildcard (*). The wildcard can also be the only character in a dynamic field name. Multiple wildcards, and wildcards embedded within a string are not supported. The name score is reserved and cannot be used as a field name. To reference a document's ID, you can use the name _id .

IndexFieldStatus

data IndexFieldStatus Source #

The value of an IndexField and its current status.

See: indexFieldStatus smart constructor.

Instances

Eq IndexFieldStatus Source # 
Data IndexFieldStatus Source # 

Methods

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

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

toConstr :: IndexFieldStatus -> Constr #

dataTypeOf :: IndexFieldStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IndexFieldStatus Source # 
Show IndexFieldStatus Source # 
Generic IndexFieldStatus Source # 
Hashable IndexFieldStatus Source # 
NFData IndexFieldStatus Source # 

Methods

rnf :: IndexFieldStatus -> () #

FromXML IndexFieldStatus Source # 
type Rep IndexFieldStatus Source # 
type Rep IndexFieldStatus = D1 * (MetaData "IndexFieldStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "IndexFieldStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifsOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * IndexField)) (S1 * (MetaSel (Just Symbol "_ifsStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionStatus))))

indexFieldStatus Source #

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

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

IntArrayOptions

data IntArrayOptions Source #

Options for a field that contains an array of 64-bit signed integers. Present if IndexFieldType specifies the field is of type int-array . All options are enabled by default.

See: intArrayOptions smart constructor.

Instances

Eq IntArrayOptions Source # 
Data IntArrayOptions Source # 

Methods

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

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

toConstr :: IntArrayOptions -> Constr #

dataTypeOf :: IntArrayOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IntArrayOptions Source # 
Show IntArrayOptions Source # 
Generic IntArrayOptions Source # 
Hashable IntArrayOptions Source # 
NFData IntArrayOptions Source # 

Methods

rnf :: IntArrayOptions -> () #

FromXML IntArrayOptions Source # 
ToQuery IntArrayOptions Source # 
type Rep IntArrayOptions Source # 
type Rep IntArrayOptions = D1 * (MetaData "IntArrayOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "IntArrayOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iaoSourceFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iaoReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iaoFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iaoSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_iaoDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer)))))))

intArrayOptions :: IntArrayOptions Source #

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

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

  • iaoSourceFields - A list of source fields to map to the field.
  • iaoReturnEnabled - Whether the contents of the field can be returned in the search results.
  • iaoFacetEnabled - Whether facet information can be returned for the field.
  • iaoSearchEnabled - Whether the contents of the field are searchable.
  • iaoDefaultValue - A value to use for the field if the field isn't specified for a document.

iaoSourceFields :: Lens' IntArrayOptions (Maybe Text) Source #

A list of source fields to map to the field.

iaoReturnEnabled :: Lens' IntArrayOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

iaoFacetEnabled :: Lens' IntArrayOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

iaoSearchEnabled :: Lens' IntArrayOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

iaoDefaultValue :: Lens' IntArrayOptions (Maybe Integer) Source #

A value to use for the field if the field isn't specified for a document.

IntOptions

data IntOptions Source #

Options for a 64-bit signed integer field. Present if IndexFieldType specifies the field is of type int . All options are enabled by default.

See: intOptions smart constructor.

Instances

Eq IntOptions Source # 
Data IntOptions Source # 

Methods

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

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

toConstr :: IntOptions -> Constr #

dataTypeOf :: IntOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IntOptions Source # 
Show IntOptions Source # 
Generic IntOptions Source # 

Associated Types

type Rep IntOptions :: * -> * #

Hashable IntOptions Source # 
NFData IntOptions Source # 

Methods

rnf :: IntOptions -> () #

FromXML IntOptions Source # 
ToQuery IntOptions Source # 
type Rep IntOptions Source # 
type Rep IntOptions = D1 * (MetaData "IntOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "IntOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ioSourceField") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ioReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_ioFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ioSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ioSortEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_ioDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer)))))))

intOptions :: IntOptions Source #

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

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

  • ioSourceField - The name of the source field to map to the field.
  • ioReturnEnabled - Whether the contents of the field can be returned in the search results.
  • ioFacetEnabled - Whether facet information can be returned for the field.
  • ioSearchEnabled - Whether the contents of the field are searchable.
  • ioSortEnabled - Whether the field can be used to sort the search results.
  • ioDefaultValue - A value to use for the field if the field isn't specified for a document. This can be important if you are using the field in an expression and that field is not present in every document.

ioSourceField :: Lens' IntOptions (Maybe Text) Source #

The name of the source field to map to the field.

ioReturnEnabled :: Lens' IntOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

ioFacetEnabled :: Lens' IntOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

ioSearchEnabled :: Lens' IntOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

ioSortEnabled :: Lens' IntOptions (Maybe Bool) Source #

Whether the field can be used to sort the search results.

ioDefaultValue :: Lens' IntOptions (Maybe Integer) Source #

A value to use for the field if the field isn't specified for a document. This can be important if you are using the field in an expression and that field is not present in every document.

LatLonOptions

data LatLonOptions Source #

Options for a latlon field. A latlon field contains a location stored as a latitude and longitude value pair. Present if IndexFieldType specifies the field is of type latlon . All options are enabled by default.

See: latLonOptions smart constructor.

Instances

Eq LatLonOptions Source # 
Data LatLonOptions Source # 

Methods

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

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

toConstr :: LatLonOptions -> Constr #

dataTypeOf :: LatLonOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LatLonOptions Source # 
Show LatLonOptions Source # 
Generic LatLonOptions Source # 

Associated Types

type Rep LatLonOptions :: * -> * #

Hashable LatLonOptions Source # 
NFData LatLonOptions Source # 

Methods

rnf :: LatLonOptions -> () #

FromXML LatLonOptions Source # 
ToQuery LatLonOptions Source # 
type Rep LatLonOptions Source # 
type Rep LatLonOptions = D1 * (MetaData "LatLonOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "LatLonOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lloSourceField") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lloReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_lloFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lloSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lloSortEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_lloDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

latLonOptions :: LatLonOptions Source #

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

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

lloReturnEnabled :: Lens' LatLonOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

lloFacetEnabled :: Lens' LatLonOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

lloSearchEnabled :: Lens' LatLonOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

lloSortEnabled :: Lens' LatLonOptions (Maybe Bool) Source #

Whether the field can be used to sort the search results.

lloDefaultValue :: Lens' LatLonOptions (Maybe Text) Source #

A value to use for the field if the field isn't specified for a document.

Limits

data Limits Source #

See: limits smart constructor.

Instances

Eq Limits Source # 

Methods

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

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

Data Limits Source # 

Methods

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

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

toConstr :: Limits -> Constr #

dataTypeOf :: Limits -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Limits Source # 
Show Limits Source # 
Generic Limits Source # 

Associated Types

type Rep Limits :: * -> * #

Methods

from :: Limits -> Rep Limits x #

to :: Rep Limits x -> Limits #

Hashable Limits Source # 

Methods

hashWithSalt :: Int -> Limits -> Int #

hash :: Limits -> Int #

NFData Limits Source # 

Methods

rnf :: Limits -> () #

FromXML Limits Source # 
type Rep Limits Source # 
type Rep Limits = D1 * (MetaData "Limits" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "Limits'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lMaximumReplicationCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat)) (S1 * (MetaSel (Just Symbol "_lMaximumPartitionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat))))

limits Source #

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

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

LiteralArrayOptions

data LiteralArrayOptions Source #

Options for a field that contains an array of literal strings. Present if IndexFieldType specifies the field is of type literal-array . All options are enabled by default.

See: literalArrayOptions smart constructor.

Instances

Eq LiteralArrayOptions Source # 
Data LiteralArrayOptions Source # 

Methods

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

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

toConstr :: LiteralArrayOptions -> Constr #

dataTypeOf :: LiteralArrayOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LiteralArrayOptions Source # 
Show LiteralArrayOptions Source # 
Generic LiteralArrayOptions Source # 
Hashable LiteralArrayOptions Source # 
NFData LiteralArrayOptions Source # 

Methods

rnf :: LiteralArrayOptions -> () #

FromXML LiteralArrayOptions Source # 
ToQuery LiteralArrayOptions Source # 
type Rep LiteralArrayOptions Source # 
type Rep LiteralArrayOptions = D1 * (MetaData "LiteralArrayOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "LiteralArrayOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_laoSourceFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_laoReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_laoFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_laoSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_laoDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

literalArrayOptions :: LiteralArrayOptions Source #

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

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

  • laoSourceFields - A list of source fields to map to the field.
  • laoReturnEnabled - Whether the contents of the field can be returned in the search results.
  • laoFacetEnabled - Whether facet information can be returned for the field.
  • laoSearchEnabled - Whether the contents of the field are searchable.
  • laoDefaultValue - A value to use for the field if the field isn't specified for a document.

laoSourceFields :: Lens' LiteralArrayOptions (Maybe Text) Source #

A list of source fields to map to the field.

laoReturnEnabled :: Lens' LiteralArrayOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

laoFacetEnabled :: Lens' LiteralArrayOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

laoSearchEnabled :: Lens' LiteralArrayOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

laoDefaultValue :: Lens' LiteralArrayOptions (Maybe Text) Source #

A value to use for the field if the field isn't specified for a document.

LiteralOptions

data LiteralOptions Source #

Options for literal field. Present if IndexFieldType specifies the field is of type literal . All options are enabled by default.

See: literalOptions smart constructor.

Instances

Eq LiteralOptions Source # 
Data LiteralOptions Source # 

Methods

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

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

toConstr :: LiteralOptions -> Constr #

dataTypeOf :: LiteralOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LiteralOptions Source # 
Show LiteralOptions Source # 
Generic LiteralOptions Source # 

Associated Types

type Rep LiteralOptions :: * -> * #

Hashable LiteralOptions Source # 
NFData LiteralOptions Source # 

Methods

rnf :: LiteralOptions -> () #

FromXML LiteralOptions Source # 
ToQuery LiteralOptions Source # 
type Rep LiteralOptions Source # 
type Rep LiteralOptions = D1 * (MetaData "LiteralOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "LiteralOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_loSourceField") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_loReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_loFacetEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_loSearchEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_loSortEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_loDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

literalOptions :: LiteralOptions Source #

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

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

  • loSourceField - Undocumented member.
  • loReturnEnabled - Whether the contents of the field can be returned in the search results.
  • loFacetEnabled - Whether facet information can be returned for the field.
  • loSearchEnabled - Whether the contents of the field are searchable.
  • loSortEnabled - Whether the field can be used to sort the search results.
  • loDefaultValue - A value to use for the field if the field isn't specified for a document.

loReturnEnabled :: Lens' LiteralOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

loFacetEnabled :: Lens' LiteralOptions (Maybe Bool) Source #

Whether facet information can be returned for the field.

loSearchEnabled :: Lens' LiteralOptions (Maybe Bool) Source #

Whether the contents of the field are searchable.

loSortEnabled :: Lens' LiteralOptions (Maybe Bool) Source #

Whether the field can be used to sort the search results.

loDefaultValue :: Lens' LiteralOptions (Maybe Text) Source #

A value to use for the field if the field isn't specified for a document.

OptionStatus

data OptionStatus Source #

The status of domain configuration option.

See: optionStatus smart constructor.

Instances

Eq OptionStatus Source # 
Data OptionStatus Source # 

Methods

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

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

toConstr :: OptionStatus -> Constr #

dataTypeOf :: OptionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OptionStatus Source # 
Show OptionStatus Source # 
Generic OptionStatus Source # 

Associated Types

type Rep OptionStatus :: * -> * #

Hashable OptionStatus Source # 
NFData OptionStatus Source # 

Methods

rnf :: OptionStatus -> () #

FromXML OptionStatus Source # 
type Rep OptionStatus Source # 
type Rep OptionStatus = D1 * (MetaData "OptionStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "OptionStatus'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_osPendingDeletion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_osUpdateVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_osCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ISO8601)) ((:*:) * (S1 * (MetaSel (Just Symbol "_osUpdateDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ISO8601)) (S1 * (MetaSel (Just Symbol "_osState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionState))))))

optionStatus Source #

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

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

  • osPendingDeletion - Indicates that the option will be deleted once processing is complete.
  • osUpdateVersion - A unique integer that indicates when this option was last updated.
  • osCreationDate - A timestamp for when this option was created.
  • osUpdateDate - A timestamp for when this option was last updated.
  • osState - The state of processing a change to an option. Possible values: * RequiresIndexDocuments : the option's latest value will not be deployed until IndexDocuments has been called and indexing is complete. * Processing : the option's latest value is in the process of being activated. * Active : the option's latest value is completely deployed. * FailedToValidate : the option value is not compatible with the domain's data and cannot be used to index the data. You must either modify the option value or update or remove the incompatible documents.

osPendingDeletion :: Lens' OptionStatus (Maybe Bool) Source #

Indicates that the option will be deleted once processing is complete.

osUpdateVersion :: Lens' OptionStatus (Maybe Natural) Source #

A unique integer that indicates when this option was last updated.

osCreationDate :: Lens' OptionStatus UTCTime Source #

A timestamp for when this option was created.

osUpdateDate :: Lens' OptionStatus UTCTime Source #

A timestamp for when this option was last updated.

osState :: Lens' OptionStatus OptionState Source #

The state of processing a change to an option. Possible values: * RequiresIndexDocuments : the option's latest value will not be deployed until IndexDocuments has been called and indexing is complete. * Processing : the option's latest value is in the process of being activated. * Active : the option's latest value is completely deployed. * FailedToValidate : the option value is not compatible with the domain's data and cannot be used to index the data. You must either modify the option value or update or remove the incompatible documents.

ScalingParameters

data ScalingParameters Source #

The desired instance type and desired number of replicas of each index partition.

See: scalingParameters smart constructor.

Instances

Eq ScalingParameters Source # 
Data ScalingParameters Source # 

Methods

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

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

toConstr :: ScalingParameters -> Constr #

dataTypeOf :: ScalingParameters -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ScalingParameters Source # 
Show ScalingParameters Source # 
Generic ScalingParameters Source # 
Hashable ScalingParameters Source # 
NFData ScalingParameters Source # 

Methods

rnf :: ScalingParameters -> () #

FromXML ScalingParameters Source # 
ToQuery ScalingParameters Source # 
type Rep ScalingParameters Source # 
type Rep ScalingParameters = D1 * (MetaData "ScalingParameters" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "ScalingParameters'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_spDesiredInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PartitionInstanceType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_spDesiredReplicationCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_spDesiredPartitionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))))))

scalingParameters :: ScalingParameters Source #

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

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

  • spDesiredInstanceType - The instance type that you want to preconfigure for your domain. For example, search.m1.small .
  • spDesiredReplicationCount - The number of replicas you want to preconfigure for each index partition.
  • spDesiredPartitionCount - The number of partitions you want to preconfigure for your domain. Only valid when you select m2.2xlarge as the desired instance type.

spDesiredInstanceType :: Lens' ScalingParameters (Maybe PartitionInstanceType) Source #

The instance type that you want to preconfigure for your domain. For example, search.m1.small .

spDesiredReplicationCount :: Lens' ScalingParameters (Maybe Natural) Source #

The number of replicas you want to preconfigure for each index partition.

spDesiredPartitionCount :: Lens' ScalingParameters (Maybe Natural) Source #

The number of partitions you want to preconfigure for your domain. Only valid when you select m2.2xlarge as the desired instance type.

ScalingParametersStatus

data ScalingParametersStatus Source #

The status and configuration of a search domain's scaling parameters.

See: scalingParametersStatus smart constructor.

Instances

Eq ScalingParametersStatus Source # 
Data ScalingParametersStatus Source # 

Methods

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

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

toConstr :: ScalingParametersStatus -> Constr #

dataTypeOf :: ScalingParametersStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ScalingParametersStatus Source # 
Show ScalingParametersStatus Source # 
Generic ScalingParametersStatus Source # 
Hashable ScalingParametersStatus Source # 
NFData ScalingParametersStatus Source # 

Methods

rnf :: ScalingParametersStatus -> () #

FromXML ScalingParametersStatus Source # 
type Rep ScalingParametersStatus Source # 
type Rep ScalingParametersStatus = D1 * (MetaData "ScalingParametersStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "ScalingParametersStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_spsOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ScalingParameters)) (S1 * (MetaSel (Just Symbol "_spsStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionStatus))))

scalingParametersStatus Source #

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

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

ServiceEndpoint

data ServiceEndpoint Source #

The endpoint to which service requests can be submitted.

See: serviceEndpoint smart constructor.

Instances

Eq ServiceEndpoint Source # 
Data ServiceEndpoint Source # 

Methods

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

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

toConstr :: ServiceEndpoint -> Constr #

dataTypeOf :: ServiceEndpoint -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceEndpoint Source # 
Show ServiceEndpoint Source # 
Generic ServiceEndpoint Source # 
Hashable ServiceEndpoint Source # 
NFData ServiceEndpoint Source # 

Methods

rnf :: ServiceEndpoint -> () #

FromXML ServiceEndpoint Source # 
type Rep ServiceEndpoint Source # 
type Rep ServiceEndpoint = D1 * (MetaData "ServiceEndpoint" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" True) (C1 * (MetaCons "ServiceEndpoint'" PrefixI True) (S1 * (MetaSel (Just Symbol "_seEndpoint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))

serviceEndpoint :: ServiceEndpoint Source #

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

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

seEndpoint :: Lens' ServiceEndpoint (Maybe Text) Source #

Undocumented member.

Suggester

data Suggester Source #

Configuration information for a search suggester. Each suggester has a unique name and specifies the text field you want to use for suggestions. The following options can be configured for a suggester: FuzzyMatching , SortExpression .

See: suggester smart constructor.

Instances

Eq Suggester Source # 
Data Suggester Source # 

Methods

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

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

toConstr :: Suggester -> Constr #

dataTypeOf :: Suggester -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Suggester Source # 
Show Suggester Source # 
Generic Suggester Source # 

Associated Types

type Rep Suggester :: * -> * #

Hashable Suggester Source # 
NFData Suggester Source # 

Methods

rnf :: Suggester -> () #

FromXML Suggester Source # 
ToQuery Suggester Source # 
type Rep Suggester Source # 
type Rep Suggester = D1 * (MetaData "Suggester" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "Suggester'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sSuggesterName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_sDocumentSuggesterOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DocumentSuggesterOptions))))

suggester Source #

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

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

sSuggesterName :: Lens' Suggester Text Source #

Undocumented member.

SuggesterStatus

data SuggesterStatus Source #

The value of a Suggester and its current status.

See: suggesterStatus smart constructor.

Instances

Eq SuggesterStatus Source # 
Data SuggesterStatus Source # 

Methods

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

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

toConstr :: SuggesterStatus -> Constr #

dataTypeOf :: SuggesterStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SuggesterStatus Source # 
Show SuggesterStatus Source # 
Generic SuggesterStatus Source # 
Hashable SuggesterStatus Source # 
NFData SuggesterStatus Source # 

Methods

rnf :: SuggesterStatus -> () #

FromXML SuggesterStatus Source # 
type Rep SuggesterStatus Source # 
type Rep SuggesterStatus = D1 * (MetaData "SuggesterStatus" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "SuggesterStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ssOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Suggester)) (S1 * (MetaSel (Just Symbol "_ssStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OptionStatus))))

suggesterStatus Source #

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

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

TextArrayOptions

data TextArrayOptions Source #

Options for a field that contains an array of text strings. Present if IndexFieldType specifies the field is of type text-array . A text-array field is always searchable. All options are enabled by default.

See: textArrayOptions smart constructor.

Instances

Eq TextArrayOptions Source # 
Data TextArrayOptions Source # 

Methods

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

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

toConstr :: TextArrayOptions -> Constr #

dataTypeOf :: TextArrayOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TextArrayOptions Source # 
Show TextArrayOptions Source # 
Generic TextArrayOptions Source # 
Hashable TextArrayOptions Source # 
NFData TextArrayOptions Source # 

Methods

rnf :: TextArrayOptions -> () #

FromXML TextArrayOptions Source # 
ToQuery TextArrayOptions Source # 
type Rep TextArrayOptions Source # 
type Rep TextArrayOptions = D1 * (MetaData "TextArrayOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "TextArrayOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_taoSourceFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_taoReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_taoAnalysisScheme") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_taoHighlightEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_taoDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

textArrayOptions :: TextArrayOptions Source #

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

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

taoSourceFields :: Lens' TextArrayOptions (Maybe Text) Source #

A list of source fields to map to the field.

taoReturnEnabled :: Lens' TextArrayOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

taoAnalysisScheme :: Lens' TextArrayOptions (Maybe Text) Source #

The name of an analysis scheme for a text-array field.

taoHighlightEnabled :: Lens' TextArrayOptions (Maybe Bool) Source #

Whether highlights can be returned for the field.

taoDefaultValue :: Lens' TextArrayOptions (Maybe Text) Source #

A value to use for the field if the field isn't specified for a document.

TextOptions

data TextOptions Source #

Options for text field. Present if IndexFieldType specifies the field is of type text . A text field is always searchable. All options are enabled by default.

See: textOptions smart constructor.

Instances

Eq TextOptions Source # 
Data TextOptions Source # 

Methods

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

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

toConstr :: TextOptions -> Constr #

dataTypeOf :: TextOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TextOptions Source # 
Show TextOptions Source # 
Generic TextOptions Source # 

Associated Types

type Rep TextOptions :: * -> * #

Hashable TextOptions Source # 
NFData TextOptions Source # 

Methods

rnf :: TextOptions -> () #

FromXML TextOptions Source # 
ToQuery TextOptions Source # 
type Rep TextOptions Source # 
type Rep TextOptions = D1 * (MetaData "TextOptions" "Network.AWS.CloudSearch.Types.Product" "amazonka-cloudsearch-1.6.0-FqLbtgWX59z7wIOS2Mnl98" False) (C1 * (MetaCons "TextOptions'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_toSourceField") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_toReturnEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_toAnalysisScheme") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_toHighlightEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_toSortEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_toDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

textOptions :: TextOptions Source #

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

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

toSourceField :: Lens' TextOptions (Maybe Text) Source #

Undocumented member.

toReturnEnabled :: Lens' TextOptions (Maybe Bool) Source #

Whether the contents of the field can be returned in the search results.

toAnalysisScheme :: Lens' TextOptions (Maybe Text) Source #

The name of an analysis scheme for a text field.

toHighlightEnabled :: Lens' TextOptions (Maybe Bool) Source #

Whether highlights can be returned for the field.

toSortEnabled :: Lens' TextOptions (Maybe Bool) Source #

Whether the field can be used to sort the search results.

toDefaultValue :: Lens' TextOptions (Maybe Text) Source #

A value to use for the field if the field isn't specified for a document.