amazonka-sdb-1.6.1: Amazon SimpleDB 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.SDB.Types

Contents

Description

 
Synopsis

Service Configuration

sdb :: Service Source #

API version 2009-04-15 of the Amazon SimpleDB SDK configuration.

Errors

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

Too many predicates exist in the query expression.

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

The specified domain does not exist.

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

Too many items exist in a single call.

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

The specified attribute does not exist.

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

Too many attributes in this domain.

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

The item name was specified more than once.

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

The request must contain the specified missing parameter.

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

The specified NextToken is not valid.

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

The value for a parameter is invalid.

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

A timeout occurred when attempting to query the specified domain with specified query expression.

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

Too many predicates exist in the query expression.

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

Too many domains exist per this account.

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

Too many attributes exist in a single call.

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

The specified query expression syntax is not valid.

Attribute

data Attribute Source #

See: attribute smart constructor.

Instances
Eq Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Data Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

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

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

toConstr :: Attribute -> Constr #

dataTypeOf :: Attribute -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Show Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Generic Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Associated Types

type Rep Attribute :: Type -> Type #

Hashable Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

FromXML Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

ToQuery Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

NFData Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

rnf :: Attribute -> () #

type Rep Attribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

type Rep Attribute = D1 (MetaData "Attribute" "Network.AWS.SDB.Types.Product" "amazonka-sdb-1.6.1-DqICC6HvLZkBMo1L4m3WLm" False) (C1 (MetaCons "Attribute'" PrefixI True) ((S1 (MetaSel (Just "_aAlternateValueEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aAlternateNameEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_aValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

attribute Source #

Arguments

:: Text

aName

-> Text

aValue

-> Attribute 

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

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

aName :: Lens' Attribute Text Source #

The name of the attribute.

aValue :: Lens' Attribute Text Source #

The value of the attribute.

DeletableItem

data DeletableItem Source #

See: deletableItem smart constructor.

Instances
Eq DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Data DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

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

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

toConstr :: DeletableItem -> Constr #

dataTypeOf :: DeletableItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Show DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Generic DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Associated Types

type Rep DeletableItem :: Type -> Type #

Hashable DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

ToQuery DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

NFData DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

rnf :: DeletableItem -> () #

type Rep DeletableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

type Rep DeletableItem = D1 (MetaData "DeletableItem" "Network.AWS.SDB.Types.Product" "amazonka-sdb-1.6.1-DqICC6HvLZkBMo1L4m3WLm" False) (C1 (MetaCons "DeletableItem'" PrefixI True) (S1 (MetaSel (Just "_diAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Attribute])) :*: S1 (MetaSel (Just "_diName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

deletableItem Source #

Arguments

:: Text

diName

-> DeletableItem 

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

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

diName :: Lens' DeletableItem Text Source #

Undocumented member.

Item

data Item Source #

See: item smart constructor.

Instances
Eq Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

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

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

Data Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

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

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

toConstr :: Item -> Constr #

dataTypeOf :: Item -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Show Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

Generic Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Associated Types

type Rep Item :: Type -> Type #

Methods

from :: Item -> Rep Item x #

to :: Rep Item x -> Item #

Hashable Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

hashWithSalt :: Int -> Item -> Int #

hash :: Item -> Int #

FromXML Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

parseXML :: [Node] -> Either String Item #

NFData Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

rnf :: Item -> () #

type Rep Item Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

type Rep Item = D1 (MetaData "Item" "Network.AWS.SDB.Types.Product" "amazonka-sdb-1.6.1-DqICC6HvLZkBMo1L4m3WLm" False) (C1 (MetaCons "Item'" PrefixI True) (S1 (MetaSel (Just "_iAlternateNameEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_iName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_iAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Attribute]))))

item Source #

Arguments

:: Text

iName

-> Item 

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

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

iName :: Lens' Item Text Source #

The name of the item.

iAttributes :: Lens' Item [Attribute] Source #

A list of attributes.

ReplaceableAttribute

data ReplaceableAttribute Source #

See: replaceableAttribute smart constructor.

Instances
Eq ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Data ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

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

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

toConstr :: ReplaceableAttribute -> Constr #

dataTypeOf :: ReplaceableAttribute -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Show ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Generic ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Associated Types

type Rep ReplaceableAttribute :: Type -> Type #

Hashable ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

ToQuery ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

NFData ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

rnf :: ReplaceableAttribute -> () #

type Rep ReplaceableAttribute Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

type Rep ReplaceableAttribute = D1 (MetaData "ReplaceableAttribute" "Network.AWS.SDB.Types.Product" "amazonka-sdb-1.6.1-DqICC6HvLZkBMo1L4m3WLm" False) (C1 (MetaCons "ReplaceableAttribute'" PrefixI True) (S1 (MetaSel (Just "_raReplace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_raName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_raValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

replaceableAttribute Source #

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

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

  • raReplace - false
  • raName - The name of the replaceable attribute.
  • raValue - The value of the replaceable attribute.

raName :: Lens' ReplaceableAttribute Text Source #

The name of the replaceable attribute.

raValue :: Lens' ReplaceableAttribute Text Source #

The value of the replaceable attribute.

ReplaceableItem

data ReplaceableItem Source #

See: replaceableItem smart constructor.

Instances
Eq ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Data ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

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

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

toConstr :: ReplaceableItem -> Constr #

dataTypeOf :: ReplaceableItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Show ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Generic ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Associated Types

type Rep ReplaceableItem :: Type -> Type #

Hashable ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

ToQuery ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

NFData ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

rnf :: ReplaceableItem -> () #

type Rep ReplaceableItem Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

type Rep ReplaceableItem = D1 (MetaData "ReplaceableItem" "Network.AWS.SDB.Types.Product" "amazonka-sdb-1.6.1-DqICC6HvLZkBMo1L4m3WLm" False) (C1 (MetaCons "ReplaceableItem'" PrefixI True) (S1 (MetaSel (Just "_riName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_riAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ReplaceableAttribute])))

replaceableItem Source #

Arguments

:: Text

riName

-> ReplaceableItem 

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

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

  • riName - The name of the replaceable item.
  • riAttributes - The list of attributes for a replaceable item.

riName :: Lens' ReplaceableItem Text Source #

The name of the replaceable item.

riAttributes :: Lens' ReplaceableItem [ReplaceableAttribute] Source #

The list of attributes for a replaceable item.

UpdateCondition

data UpdateCondition Source #

Specifies the conditions under which data should be updated. If an update condition is specified for a request, the data will only be updated if the condition is satisfied. For example, if an attribute with a specific name and value exists, or if a specific attribute doesn't exist.

See: updateCondition smart constructor.

Instances
Eq UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Data UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

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

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

toConstr :: UpdateCondition -> Constr #

dataTypeOf :: UpdateCondition -> DataType #

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

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

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

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

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

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

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

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

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

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

Read UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Show UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Generic UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Associated Types

type Rep UpdateCondition :: Type -> Type #

Hashable UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

ToQuery UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

NFData UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

Methods

rnf :: UpdateCondition -> () #

type Rep UpdateCondition Source # 
Instance details

Defined in Network.AWS.SDB.Types.Product

type Rep UpdateCondition = D1 (MetaData "UpdateCondition" "Network.AWS.SDB.Types.Product" "amazonka-sdb-1.6.1-DqICC6HvLZkBMo1L4m3WLm" False) (C1 (MetaCons "UpdateCondition'" PrefixI True) (S1 (MetaSel (Just "_ucExists") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_ucValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ucName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

updateCondition :: UpdateCondition Source #

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

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

  • ucExists - A value specifying whether or not the specified attribute must exist with the specified value in order for the update condition to be satisfied. Specify true if the attribute must exist for the update condition to be satisfied. Specify false if the attribute should not exist in order for the update condition to be satisfied.
  • ucValue - The value of an attribute. This value can only be specified when the Exists parameter is equal to true .
  • ucName - The name of the attribute involved in the condition.

ucExists :: Lens' UpdateCondition (Maybe Bool) Source #

A value specifying whether or not the specified attribute must exist with the specified value in order for the update condition to be satisfied. Specify true if the attribute must exist for the update condition to be satisfied. Specify false if the attribute should not exist in order for the update condition to be satisfied.

ucValue :: Lens' UpdateCondition (Maybe Text) Source #

The value of an attribute. This value can only be specified when the Exists parameter is equal to true .

ucName :: Lens' UpdateCondition (Maybe Text) Source #

The name of the attribute involved in the condition.