amazonka-dynamodb-dax-1.6.1: Amazon DynamoDB Accelerator (DAX) 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.DAX.Types

Contents

Description

 
Synopsis

Service Configuration

dax :: Service Source #

API version 2017-04-19 of the Amazon DynamoDB Accelerator (DAX) SDK configuration.

Errors

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

The request cannot be processed because it would exceed the allowed number of subnets in a subnet group.

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

The specified parameter group does not exist.

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

One or more parameters in a parameter group are in an invalid state.

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

The specified subnet group is currently in use.

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

The specified parameter group already exists.

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

An invalid subnet identifier was specified.

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

You have exceeded the maximum number of tags for this DAX cluster.

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

The requested cluster ID does not refer to an existing DAX cluster.

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

You have attempted to exceed the maximum number of nodes for a DAX cluster.

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

The requested DAX cluster is not in the available state.

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

There are not enough system resources to create the cluster you requested (or to resize an already-existing cluster).

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

None of the nodes in the cluster have the given node ID.

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

You have attempted to exceed the maximum number of parameter groups.

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

The value for a parameter is invalid.

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

The VPC network is in an invalid state.

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

The requested subnet is being used by another subnet group.

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

You have attempted to exceed the maximum number of DAX clusters for your AWS account.

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

The requested subnet group name does not refer to an existing subnet group.

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

The specified subnet group already exists.

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

You have attempted to exceed the maximum number of nodes for your AWS account.

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

The request cannot be processed because it would exceed the allowed number of subnets in a subnet group.

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

You already have a DAX cluster with the given identifier.

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

The Amazon Resource Name (ARN) supplied in the request is not valid.

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

Two or more incompatible parameters were specified.

ChangeType

data ChangeType Source #

Constructors

Immediate 
RequiresReboot 
Instances
Bounded ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Enum ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Eq ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Data ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

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

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

toConstr :: ChangeType -> Constr #

dataTypeOf :: ChangeType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Read ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Show ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Generic ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Associated Types

type Rep ChangeType :: Type -> Type #

Hashable ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromJSON ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToHeader ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToQuery ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToByteString ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromText ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToText ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

toText :: ChangeType -> Text #

NFData ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

rnf :: ChangeType -> () #

type Rep ChangeType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

type Rep ChangeType = D1 (MetaData "ChangeType" "Network.AWS.DAX.Types.Sum" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Immediate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RequiresReboot" PrefixI False) (U1 :: Type -> Type))

IsModifiable

data IsModifiable Source #

Constructors

Conditional 
False' 
True' 
Instances
Bounded IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Enum IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Eq IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Data IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

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

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

toConstr :: IsModifiable -> Constr #

dataTypeOf :: IsModifiable -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Read IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Show IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Generic IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Associated Types

type Rep IsModifiable :: Type -> Type #

Hashable IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromJSON IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToHeader IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToQuery IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToByteString IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromText IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToText IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

toText :: IsModifiable -> Text #

NFData IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

rnf :: IsModifiable -> () #

type Rep IsModifiable Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

type Rep IsModifiable = D1 (MetaData "IsModifiable" "Network.AWS.DAX.Types.Sum" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Conditional" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "False'" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "True'" PrefixI False) (U1 :: Type -> Type)))

ParameterType

data ParameterType Source #

Constructors

Default 
NodeTypeSpecific 
Instances
Bounded ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Enum ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Eq ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Data ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

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

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

toConstr :: ParameterType -> Constr #

dataTypeOf :: ParameterType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Read ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Show ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Generic ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Associated Types

type Rep ParameterType :: Type -> Type #

Hashable ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromJSON ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToHeader ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToQuery ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToByteString ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromText ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToText ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

toText :: ParameterType -> Text #

NFData ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

rnf :: ParameterType -> () #

type Rep ParameterType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

type Rep ParameterType = D1 (MetaData "ParameterType" "Network.AWS.DAX.Types.Sum" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Default" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NodeTypeSpecific" PrefixI False) (U1 :: Type -> Type))

SourceType

data SourceType Source #

Instances
Bounded SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Enum SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Eq SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Data SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

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

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

toConstr :: SourceType -> Constr #

dataTypeOf :: SourceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Read SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Show SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Generic SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Associated Types

type Rep SourceType :: Type -> Type #

Hashable SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToJSON SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromJSON SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToHeader SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToQuery SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToByteString SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

FromText SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

ToText SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

toText :: SourceType -> Text #

NFData SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

Methods

rnf :: SourceType -> () #

type Rep SourceType Source # 
Instance details

Defined in Network.AWS.DAX.Types.Sum

type Rep SourceType = D1 (MetaData "SourceType" "Network.AWS.DAX.Types.Sum" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Cluster" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ParameterGroup" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SubnetGroup" PrefixI False) (U1 :: Type -> Type)))

Cluster

data Cluster Source #

Contains all of the attributes of a specific DAX cluster.

See: cluster smart constructor.

Instances
Eq Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

Data Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: Cluster -> Constr #

dataTypeOf :: Cluster -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep Cluster :: Type -> Type #

Methods

from :: Cluster -> Rep Cluster x #

to :: Rep Cluster x -> Cluster #

Hashable Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

hashWithSalt :: Int -> Cluster -> Int #

hash :: Cluster -> Int #

FromJSON Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: Cluster -> () #

type Rep Cluster Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep Cluster = D1 (MetaData "Cluster" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Cluster'" PrefixI True) ((((S1 (MetaSel (Just "_cStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cIAMRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_cClusterARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cActiveNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) :*: ((S1 (MetaSel (Just "_cSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SecurityGroupMembership])) :*: S1 (MetaSel (Just "_cNotificationConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NotificationConfiguration))) :*: (S1 (MetaSel (Just "_cNodeIdsToRemove") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_cTotalNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))) :*: (((S1 (MetaSel (Just "_cPreferredMaintenanceWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cSubnetGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_cClusterName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_cNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Node])) :*: S1 (MetaSel (Just "_cClusterDiscoveryEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Endpoint))) :*: (S1 (MetaSel (Just "_cDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cParameterGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ParameterGroupStatus)))))))

cluster :: Cluster Source #

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

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

  • cStatus - The current status of the cluster.
  • cIAMRoleARN - A valid Amazon Resource Name (ARN) that identifies an IAM role. At runtime, DAX will assume this role and use the role's permissions to access DynamoDB on your behalf.
  • cClusterARN - The Amazon Resource Name (ARN) that uniquely identifies the cluster.
  • cActiveNodes - The number of nodes in the cluster that are active (i.e., capable of serving requests).
  • cSecurityGroups - A list of security groups, and the status of each, for the nodes in the cluster.
  • cNotificationConfiguration - Describes a notification topic and its status. Notification topics are used for publishing DAX events to subscribers using Amazon Simple Notification Service (SNS).
  • cNodeIdsToRemove - A list of nodes to be removed from the cluster.
  • cTotalNodes - The total number of nodes in the cluster.
  • cPreferredMaintenanceWindow - A range of time when maintenance of DAX cluster software will be performed. For example: sun:01:00-sun:09:00 . Cluster maintenance normally takes less than 30 minutes, and is performed automatically within the maintenance window.
  • cSubnetGroup - The subnet group where the DAX cluster is running.
  • cClusterName - The name of the DAX cluster.
  • cNodeType - The node type for the nodes in the cluster. (All nodes in a DAX cluster are of the same type.)
  • cNodes - A list of nodes that are currently in the cluster.
  • cClusterDiscoveryEndpoint - The configuration endpoint for this DAX cluster, consisting of a DNS name and a port number. Client applications can specify this endpoint, rather than an individual node endpoint, and allow the DAX client software to intelligently route requests and responses to nodes in the DAX cluster.
  • cDescription - The description of the cluster.
  • cParameterGroup - The parameter group being used by nodes in the cluster.

cStatus :: Lens' Cluster (Maybe Text) Source #

The current status of the cluster.

cIAMRoleARN :: Lens' Cluster (Maybe Text) Source #

A valid Amazon Resource Name (ARN) that identifies an IAM role. At runtime, DAX will assume this role and use the role's permissions to access DynamoDB on your behalf.

cClusterARN :: Lens' Cluster (Maybe Text) Source #

The Amazon Resource Name (ARN) that uniquely identifies the cluster.

cActiveNodes :: Lens' Cluster (Maybe Int) Source #

The number of nodes in the cluster that are active (i.e., capable of serving requests).

cSecurityGroups :: Lens' Cluster [SecurityGroupMembership] Source #

A list of security groups, and the status of each, for the nodes in the cluster.

cNotificationConfiguration :: Lens' Cluster (Maybe NotificationConfiguration) Source #

Describes a notification topic and its status. Notification topics are used for publishing DAX events to subscribers using Amazon Simple Notification Service (SNS).

cNodeIdsToRemove :: Lens' Cluster [Text] Source #

A list of nodes to be removed from the cluster.

cTotalNodes :: Lens' Cluster (Maybe Int) Source #

The total number of nodes in the cluster.

cPreferredMaintenanceWindow :: Lens' Cluster (Maybe Text) Source #

A range of time when maintenance of DAX cluster software will be performed. For example: sun:01:00-sun:09:00 . Cluster maintenance normally takes less than 30 minutes, and is performed automatically within the maintenance window.

cSubnetGroup :: Lens' Cluster (Maybe Text) Source #

The subnet group where the DAX cluster is running.

cClusterName :: Lens' Cluster (Maybe Text) Source #

The name of the DAX cluster.

cNodeType :: Lens' Cluster (Maybe Text) Source #

The node type for the nodes in the cluster. (All nodes in a DAX cluster are of the same type.)

cNodes :: Lens' Cluster [Node] Source #

A list of nodes that are currently in the cluster.

cClusterDiscoveryEndpoint :: Lens' Cluster (Maybe Endpoint) Source #

The configuration endpoint for this DAX cluster, consisting of a DNS name and a port number. Client applications can specify this endpoint, rather than an individual node endpoint, and allow the DAX client software to intelligently route requests and responses to nodes in the DAX cluster.

cDescription :: Lens' Cluster (Maybe Text) Source #

The description of the cluster.

cParameterGroup :: Lens' Cluster (Maybe ParameterGroupStatus) Source #

The parameter group being used by nodes in the cluster.

Endpoint

data Endpoint Source #

Represents the information required for client programs to connect to the configuration endpoint for a DAX cluster, or to an individual node within the cluster.

See: endpoint smart constructor.

Instances
Eq Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: Endpoint -> Constr #

dataTypeOf :: Endpoint -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep Endpoint :: Type -> Type #

Methods

from :: Endpoint -> Rep Endpoint x #

to :: Rep Endpoint x -> Endpoint #

Hashable Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

hashWithSalt :: Int -> Endpoint -> Int #

hash :: Endpoint -> Int #

FromJSON Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: Endpoint -> () #

type Rep Endpoint Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep Endpoint = D1 (MetaData "Endpoint" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Endpoint'" PrefixI True) (S1 (MetaSel (Just "_eAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ePort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))

endpoint :: Endpoint Source #

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

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

  • eAddress - The DNS hostname of the endpoint.
  • ePort - The port number that applications should use to connect to the endpoint.

eAddress :: Lens' Endpoint (Maybe Text) Source #

The DNS hostname of the endpoint.

ePort :: Lens' Endpoint (Maybe Int) Source #

The port number that applications should use to connect to the endpoint.

Event

data Event Source #

Represents a single occurrence of something interesting within the system. Some examples of events are creating a DAX cluster, adding or removing a node, or rebooting a node.

See: event smart constructor.

Instances
Eq Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

Data Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: Event -> Constr #

dataTypeOf :: Event -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Hashable Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

hashWithSalt :: Int -> Event -> Int #

hash :: Event -> Int #

FromJSON Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: Event -> () #

type Rep Event Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep Event = D1 (MetaData "Event" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Event'" PrefixI True) ((S1 (MetaSel (Just "_eSourceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_eSourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SourceType))) :*: (S1 (MetaSel (Just "_eDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_eMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

event :: Event Source #

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

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

  • eSourceName - The source of the event. For example, if the event occurred at the node level, the source would be the node ID.
  • eSourceType - Specifies the origin of this event - a cluster, a parameter group, a node ID, etc.
  • eDate - The date and time when the event occurred.
  • eMessage - A user-defined message associated with the event.

eSourceName :: Lens' Event (Maybe Text) Source #

The source of the event. For example, if the event occurred at the node level, the source would be the node ID.

eSourceType :: Lens' Event (Maybe SourceType) Source #

Specifies the origin of this event - a cluster, a parameter group, a node ID, etc.

eDate :: Lens' Event (Maybe UTCTime) Source #

The date and time when the event occurred.

eMessage :: Lens' Event (Maybe Text) Source #

A user-defined message associated with the event.

Node

data Node Source #

Represents an individual node within a DAX cluster.

See: node smart constructor.

Instances
Eq Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

Data Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: Node -> Constr #

dataTypeOf :: Node -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Generic Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

Hashable Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

hashWithSalt :: Int -> Node -> Int #

hash :: Node -> Int #

FromJSON Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: Node -> () #

type Rep Node Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep Node = D1 (MetaData "Node" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Node'" PrefixI True) ((S1 (MetaSel (Just "_nNodeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_nParameterGroupStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_nNodeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_nEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Endpoint)) :*: S1 (MetaSel (Just "_nNodeCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))))))

node :: Node Source #

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

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

  • nNodeStatus - The current status of the node. For example: available .
  • nParameterGroupStatus - The status of the parameter group associated with this node. For example, in-sync .
  • nAvailabilityZone - The Availability Zone (AZ) in which the node has been deployed.
  • nNodeId - A system-generated identifier for the node.
  • nEndpoint - The endpoint for the node, consisting of a DNS name and a port number. Client applications can connect directly to a node endpoint, if desired (as an alternative to allowing DAX client software to intelligently route requests and responses to nodes in the DAX cluster.
  • nNodeCreateTime - The date and time (in UNIX epoch format) when the node was launched.

nNodeStatus :: Lens' Node (Maybe Text) Source #

The current status of the node. For example: available .

nParameterGroupStatus :: Lens' Node (Maybe Text) Source #

The status of the parameter group associated with this node. For example, in-sync .

nAvailabilityZone :: Lens' Node (Maybe Text) Source #

The Availability Zone (AZ) in which the node has been deployed.

nNodeId :: Lens' Node (Maybe Text) Source #

A system-generated identifier for the node.

nEndpoint :: Lens' Node (Maybe Endpoint) Source #

The endpoint for the node, consisting of a DNS name and a port number. Client applications can connect directly to a node endpoint, if desired (as an alternative to allowing DAX client software to intelligently route requests and responses to nodes in the DAX cluster.

nNodeCreateTime :: Lens' Node (Maybe UTCTime) Source #

The date and time (in UNIX epoch format) when the node was launched.

NodeTypeSpecificValue

data NodeTypeSpecificValue Source #

Represents a parameter value that is applicable to a particular node type.

See: nodeTypeSpecificValue smart constructor.

Instances
Eq NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: NodeTypeSpecificValue -> Constr #

dataTypeOf :: NodeTypeSpecificValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep NodeTypeSpecificValue :: Type -> Type #

Hashable NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: NodeTypeSpecificValue -> () #

type Rep NodeTypeSpecificValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep NodeTypeSpecificValue = D1 (MetaData "NodeTypeSpecificValue" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "NodeTypeSpecificValue'" PrefixI True) (S1 (MetaSel (Just "_ntsvValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ntsvNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

nodeTypeSpecificValue :: NodeTypeSpecificValue Source #

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

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

  • ntsvValue - The parameter value for this node type.
  • ntsvNodeType - A node type to which the parameter value applies.

ntsvValue :: Lens' NodeTypeSpecificValue (Maybe Text) Source #

The parameter value for this node type.

ntsvNodeType :: Lens' NodeTypeSpecificValue (Maybe Text) Source #

A node type to which the parameter value applies.

NotificationConfiguration

data NotificationConfiguration Source #

Describes a notification topic and its status. Notification topics are used for publishing DAX events to subscribers using Amazon Simple Notification Service (SNS).

See: notificationConfiguration smart constructor.

Instances
Eq NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: NotificationConfiguration -> Constr #

dataTypeOf :: NotificationConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep NotificationConfiguration :: Type -> Type #

Hashable NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep NotificationConfiguration Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep NotificationConfiguration = D1 (MetaData "NotificationConfiguration" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "NotificationConfiguration'" PrefixI True) (S1 (MetaSel (Just "_ncTopicStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ncTopicARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

notificationConfiguration :: NotificationConfiguration Source #

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

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

  • ncTopicStatus - The current state of the topic.
  • ncTopicARN - The Amazon Resource Name (ARN) that identifies the topic.

ncTopicStatus :: Lens' NotificationConfiguration (Maybe Text) Source #

The current state of the topic.

ncTopicARN :: Lens' NotificationConfiguration (Maybe Text) Source #

The Amazon Resource Name (ARN) that identifies the topic.

Parameter

data Parameter Source #

Describes an individual setting that controls some aspect of DAX behavior.

See: parameter smart constructor.

Instances
Eq Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: Parameter -> Constr #

dataTypeOf :: Parameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep Parameter :: Type -> Type #

Hashable Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: Parameter -> () #

type Rep Parameter Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

parameter :: Parameter Source #

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

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

  • pParameterValue - The value for the parameter.
  • pParameterType - Determines whether the parameter can be applied to any nodes, or only nodes of a particular type.
  • pSource - How the parameter is defined. For example, system denotes a system-defined parameter.
  • pIsModifiable - Whether the customer is allowed to modify the parameter.
  • pDataType - The data type of the parameter. For example, integer :
  • pNodeTypeSpecificValues - A list of node types, and specific parameter values for each node.
  • pAllowedValues - A range of values within which the parameter can be set.
  • pParameterName - The name of the parameter.
  • pDescription - A description of the parameter
  • pChangeType - The conditions under which changes to this parameter can be applied. For example, requires-reboot indicates that a new value for this parameter will only take effect if a node is rebooted.

pParameterValue :: Lens' Parameter (Maybe Text) Source #

The value for the parameter.

pParameterType :: Lens' Parameter (Maybe ParameterType) Source #

Determines whether the parameter can be applied to any nodes, or only nodes of a particular type.

pSource :: Lens' Parameter (Maybe Text) Source #

How the parameter is defined. For example, system denotes a system-defined parameter.

pIsModifiable :: Lens' Parameter (Maybe IsModifiable) Source #

Whether the customer is allowed to modify the parameter.

pDataType :: Lens' Parameter (Maybe Text) Source #

The data type of the parameter. For example, integer :

pNodeTypeSpecificValues :: Lens' Parameter [NodeTypeSpecificValue] Source #

A list of node types, and specific parameter values for each node.

pAllowedValues :: Lens' Parameter (Maybe Text) Source #

A range of values within which the parameter can be set.

pParameterName :: Lens' Parameter (Maybe Text) Source #

The name of the parameter.

pDescription :: Lens' Parameter (Maybe Text) Source #

A description of the parameter

pChangeType :: Lens' Parameter (Maybe ChangeType) Source #

The conditions under which changes to this parameter can be applied. For example, requires-reboot indicates that a new value for this parameter will only take effect if a node is rebooted.

ParameterGroup

data ParameterGroup Source #

A named set of parameters that are applied to all of the nodes in a DAX cluster.

See: parameterGroup smart constructor.

Instances
Eq ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: ParameterGroup -> Constr #

dataTypeOf :: ParameterGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep ParameterGroup :: Type -> Type #

Hashable ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: ParameterGroup -> () #

type Rep ParameterGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep ParameterGroup = D1 (MetaData "ParameterGroup" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "ParameterGroup'" PrefixI True) (S1 (MetaSel (Just "_pgDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pgParameterGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

parameterGroup :: ParameterGroup Source #

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

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

pgDescription :: Lens' ParameterGroup (Maybe Text) Source #

A description of the parameter group.

pgParameterGroupName :: Lens' ParameterGroup (Maybe Text) Source #

The name of the parameter group.

ParameterGroupStatus

data ParameterGroupStatus Source #

The status of a parameter group.

See: parameterGroupStatus smart constructor.

Instances
Eq ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: ParameterGroupStatus -> Constr #

dataTypeOf :: ParameterGroupStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep ParameterGroupStatus :: Type -> Type #

Hashable ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: ParameterGroupStatus -> () #

type Rep ParameterGroupStatus Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep ParameterGroupStatus = D1 (MetaData "ParameterGroupStatus" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "ParameterGroupStatus'" PrefixI True) (S1 (MetaSel (Just "_pgsNodeIdsToReboot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 (MetaSel (Just "_pgsParameterApplyStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pgsParameterGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

parameterGroupStatus :: ParameterGroupStatus Source #

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

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

pgsNodeIdsToReboot :: Lens' ParameterGroupStatus [Text] Source #

The node IDs of one or more nodes to be rebooted.

pgsParameterApplyStatus :: Lens' ParameterGroupStatus (Maybe Text) Source #

The status of parameter updates.

pgsParameterGroupName :: Lens' ParameterGroupStatus (Maybe Text) Source #

The name of the parameter group.

ParameterNameValue

data ParameterNameValue Source #

An individual DAX parameter.

See: parameterNameValue smart constructor.

Instances
Eq ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: ParameterNameValue -> Constr #

dataTypeOf :: ParameterNameValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep ParameterNameValue :: Type -> Type #

Hashable ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

ToJSON ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: ParameterNameValue -> () #

type Rep ParameterNameValue Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep ParameterNameValue = D1 (MetaData "ParameterNameValue" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "ParameterNameValue'" PrefixI True) (S1 (MetaSel (Just "_pnvParameterValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pnvParameterName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

parameterNameValue :: ParameterNameValue Source #

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

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

pnvParameterValue :: Lens' ParameterNameValue (Maybe Text) Source #

The value of the parameter.

pnvParameterName :: Lens' ParameterNameValue (Maybe Text) Source #

The name of the parameter.

SecurityGroupMembership

data SecurityGroupMembership Source #

An individual VPC security group and its status.

See: securityGroupMembership smart constructor.

Instances
Eq SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: SecurityGroupMembership -> Constr #

dataTypeOf :: SecurityGroupMembership -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep SecurityGroupMembership :: Type -> Type #

Hashable SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: SecurityGroupMembership -> () #

type Rep SecurityGroupMembership Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep SecurityGroupMembership = D1 (MetaData "SecurityGroupMembership" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "SecurityGroupMembership'" PrefixI True) (S1 (MetaSel (Just "_sgmStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_sgmSecurityGroupIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

securityGroupMembership :: SecurityGroupMembership Source #

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

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

sgmStatus :: Lens' SecurityGroupMembership (Maybe Text) Source #

The status of this security group.

sgmSecurityGroupIdentifier :: Lens' SecurityGroupMembership (Maybe Text) Source #

The unique ID for this security group.

Subnet

data Subnet Source #

Represents the subnet associated with a DAX cluster. This parameter refers to subnets defined in Amazon Virtual Private Cloud (Amazon VPC) and used with DAX.

See: subnet smart constructor.

Instances
Eq Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

Data Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: Subnet -> Constr #

dataTypeOf :: Subnet -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep Subnet :: Type -> Type #

Methods

from :: Subnet -> Rep Subnet x #

to :: Rep Subnet x -> Subnet #

Hashable Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

hashWithSalt :: Int -> Subnet -> Int #

hash :: Subnet -> Int #

FromJSON Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: Subnet -> () #

type Rep Subnet Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep Subnet = D1 (MetaData "Subnet" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Subnet'" PrefixI True) (S1 (MetaSel (Just "_sSubnetIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_sSubnetAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

subnet :: Subnet Source #

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

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

sSubnetIdentifier :: Lens' Subnet (Maybe Text) Source #

The system-assigned identifier for the subnet.

sSubnetAvailabilityZone :: Lens' Subnet (Maybe Text) Source #

The Availability Zone (AZ) for subnet subnet.

SubnetGroup

data SubnetGroup Source #

Represents the output of one of the following actions:

  • CreateSubnetGroup
  • ModifySubnetGroup

See: subnetGroup smart constructor.

Instances
Eq SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Data SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: SubnetGroup -> Constr #

dataTypeOf :: SubnetGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Generic SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep SubnetGroup :: Type -> Type #

Hashable SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: SubnetGroup -> () #

type Rep SubnetGroup Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep SubnetGroup = D1 (MetaData "SubnetGroup" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "SubnetGroup'" PrefixI True) ((S1 (MetaSel (Just "_sgVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_sgSubnets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Subnet]))) :*: (S1 (MetaSel (Just "_sgSubnetGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_sgDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

subnetGroup :: SubnetGroup Source #

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

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

  • sgVPCId - The Amazon Virtual Private Cloud identifier (VPC ID) of the subnet group.
  • sgSubnets - A list of subnets associated with the subnet group.
  • sgSubnetGroupName - The name of the subnet group.
  • sgDescription - The description of the subnet group.

sgVPCId :: Lens' SubnetGroup (Maybe Text) Source #

The Amazon Virtual Private Cloud identifier (VPC ID) of the subnet group.

sgSubnets :: Lens' SubnetGroup [Subnet] Source #

A list of subnets associated with the subnet group.

sgSubnetGroupName :: Lens' SubnetGroup (Maybe Text) Source #

The name of the subnet group.

sgDescription :: Lens' SubnetGroup (Maybe Text) Source #

The description of the subnet group.

Tag

data Tag Source #

A description of a tag. Every tag is a key-value pair. You can add up to 50 tags to a single DAX cluster.

AWS-assigned tag names and values are automatically assigned the aws: prefix, which the user cannot assign. AWS-assigned tag names do not count towards the tag limit of 50. User-assigned tag names have the prefix user: .

You cannot backdate the application of a tag.

See: tag smart constructor.

Instances
Eq Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

Data Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

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

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

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Show Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

FromJSON Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

NFData Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
Instance details

Defined in Network.AWS.DAX.Types.Product

type Rep Tag = D1 (MetaData "Tag" "Network.AWS.DAX.Types.Product" "amazonka-dynamodb-dax-1.6.1-6GOQo4sHyZjF5gipywaEPV" False) (C1 (MetaCons "Tag'" PrefixI True) (S1 (MetaSel (Just "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

tag :: Tag Source #

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

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

  • tagValue - The value of the tag. Tag values are case-sensitive and can be null.
  • tagKey - The key for the tag. Tag keys are case sensitive. Every DAX cluster can only have one tag with the same key. If you try to add an existing tag (same key), the existing tag value will be updated to the new value.

tagValue :: Lens' Tag (Maybe Text) Source #

The value of the tag. Tag values are case-sensitive and can be null.

tagKey :: Lens' Tag (Maybe Text) Source #

The key for the tag. Tag keys are case sensitive. Every DAX cluster can only have one tag with the same key. If you try to add an existing tag (same key), the existing tag value will be updated to the new value.