amazonka-elasticache-1.5.0: Amazon ElastiCache SDK.

Copyright(c) 2013-2017 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.ElastiCache

Contents

Description

Amazon ElastiCache

Amazon ElastiCache is a web service that makes it easier to set up, operate, and scale a distributed cache in the cloud.

With ElastiCache, customers get all of the benefits of a high-performance, in-memory cache with less of the administrative burden involved in launching and managing a distributed cache. The service makes setup, scaling, and cluster failure handling much simpler than in a self-managed cache deployment.

In addition, through integration with Amazon CloudWatch, customers get enhanced visibility into the key performance statistics associated with their cache and can receive alarms if a part of their cache runs hot.

Synopsis

Service Configuration

elastiCache :: Service Source #

API version 2015-02-02 of the Amazon ElastiCache SDK configuration.

Errors

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

CacheSubnetGroupInUse

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

The requested cache subnet group is currently in use.

ReservedCacheNodeAlreadyExistsFault

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

You already have a reservation with the given identifier.

CacheSecurityGroupNotFoundFault

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

The requested cache security group name does not refer to an existing cache security group.

CacheSubnetGroupAlreadyExistsFault

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

The requested cache subnet group name is already in use by an existing cache subnet group.

NodeGroupsPerReplicationGroupQuotaExceededFault

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

The request cannot be processed because it would exceed the maximum allowed number of node groups (shards) in a single replication group. The default maximum is 15

CacheSubnetGroupQuotaExceededFault

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

The request cannot be processed because it would exceed the allowed number of cache subnet groups.

AuthorizationAlreadyExistsFault

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

The specified Amazon EC2 security group is already authorized for the specified cache security group.

ReservedCacheNodeQuotaExceededFault

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

The request cannot be processed because it would exceed the user's cache node quota.

ReservedCacheNodesOfferingNotFoundFault

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

The requested cache node offering does not exist.

ReplicationGroupNotFoundFault

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

The specified replication group does not exist.

InvalidSubnet

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

An invalid subnet identifier was specified.

TagQuotaPerResourceExceeded

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

The request cannot be processed because it would cause the resource to have more than the allowed number of tags. The maximum number of tags permitted on a resource is 50.

SnapshotNotFoundFault

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

The requested snapshot name does not refer to an existing snapshot.

InsufficientCacheClusterCapacityFault

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

The requested cache node type is not available in the specified Availability Zone.

InvalidSnapshotStateFault

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

The current state of the snapshot does not allow the requested operation to occur.

SnapshotAlreadyExistsFault

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

You already have a snapshot with the given name.

TagNotFoundFault

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

The requested tag was not found on this resource.

SnapshotQuotaExceededFault

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

The request cannot be processed because it would exceed the maximum number of snapshots.

NodeQuotaForClusterExceededFault

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

The request cannot be processed because it would exceed the allowed number of cache nodes in a single cluster.

APICallRateForCustomerExceededFault

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

The customer has exceeded the allowed rate of API calls.

NodeGroupNotFoundFault

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

The node group specified by the NodeGroupId parameter could not be found. Please verify that the node group exists and that you spelled the NodeGroupId value correctly.

CacheParameterGroupAlreadyExistsFault

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

A cache parameter group with the requested name already exists.

ReservedCacheNodeNotFoundFault

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

The requested reserved cache node was not found.

CacheSubnetGroupNotFoundFault

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

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

SnapshotFeatureNotSupportedFault

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

You attempted one of the following operations:

  • Creating a snapshot of a Redis cluster running on a cache.t1.micro cache node.
  • Creating a snapshot of a cluster that is running Memcached rather than Redis.

Neither of these are supported by ElastiCache.

InvalidParameterValueException

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

The value for a parameter is invalid.

TestFailoverNotAvailableFault

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

Prism for TestFailoverNotAvailableFault' errors.

InvalidReplicationGroupStateFault

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

The requested replication group is not in the available state.

ReplicationGroupAlreadyExistsFault

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

The specified replication group already exists.

InvalidVPCNetworkStateFault

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

The VPC network is in an invalid state.

SubnetInUse

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

The requested subnet is being used by another cache subnet group.

CacheClusterNotFoundFault

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

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

ClusterQuotaForCustomerExceededFault

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

The request cannot be processed because it would exceed the allowed number of clusters per customer.

AuthorizationNotFoundFault

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

The specified Amazon EC2 security group is not authorized for the specified cache security group.

InvalidCacheClusterStateFault

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

The requested cluster is not in the available state.

CacheSecurityGroupQuotaExceededFault

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

The request cannot be processed because it would exceed the allowed number of cache security groups.

CacheClusterAlreadyExistsFault

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

You already have a cluster with the given identifier.

CacheParameterGroupQuotaExceededFault

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

The request cannot be processed because it would exceed the maximum number of cache security groups.

NodeQuotaForCustomerExceededFault

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

The request cannot be processed because it would exceed the allowed number of cache nodes per customer.

CacheSubnetQuotaExceededFault

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

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

CacheParameterGroupNotFoundFault

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

The requested cache parameter group name does not refer to an existing cache parameter group.

InvalidARNFault

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

The requested Amazon Resource Name (ARN) does not refer to an existing resource.

InvalidCacheParameterGroupStateFault

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

The current state of the cache parameter group does not allow the requested operation to occur.

InvalidParameterCombinationException

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

Two or more incompatible parameters were specified.

InvalidCacheSecurityGroupStateFault

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

The current state of the cache security group does not allow deletion.

CacheSecurityGroupAlreadyExistsFault

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

A cache security group with the specified name already exists.

Waiters

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

CacheClusterAvailable

cacheClusterAvailable :: Wait DescribeCacheClusters Source #

Polls DescribeCacheClusters every 30 seconds until a successful state is reached. An error is returned after 60 failed checks.

CacheClusterDeleted

cacheClusterDeleted :: Wait DescribeCacheClusters Source #

Polls DescribeCacheClusters every 30 seconds until a successful state is reached. An error is returned after 60 failed checks.

ReplicationGroupDeleted

replicationGroupDeleted :: Wait DescribeReplicationGroups Source #

Polls DescribeReplicationGroups every 30 seconds until a successful state is reached. An error is returned after 60 failed checks.

ReplicationGroupAvailable

replicationGroupAvailable :: Wait DescribeReplicationGroups Source #

Polls DescribeReplicationGroups every 30 seconds until a successful state is reached. An error is returned after 60 failed checks.

Operations

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

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

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

DeleteCacheSecurityGroup

CreateReplicationGroup

DeleteCacheCluster

RebootCacheCluster

RevokeCacheSecurityGroupIngress

CreateCacheCluster

DescribeEvents (Paginated)

DescribeEngineDefaultParameters (Paginated)

ModifyCacheParameterGroup

TestFailover

DeleteReplicationGroup

ListTagsForResource

DescribeCacheClusters (Paginated)

PurchaseReservedCacheNodesOffering

RemoveTagsFromResource

ModifyReplicationGroup

DescribeCacheParameters (Paginated)

DescribeCacheSubnetGroups (Paginated)

CreateCacheSecurityGroup

AddTagsToResource

AuthorizeCacheSecurityGroupIngress

CopySnapshot

CreateCacheSubnetGroup

DescribeCacheParameterGroups (Paginated)

ResetCacheParameterGroup

ListAllowedNodeTypeModifications

ModifyReplicationGroupShardConfiguration

DescribeSnapshots (Paginated)

DescribeReplicationGroups (Paginated)

DeleteSnapshot

DescribeReservedCacheNodesOfferings (Paginated)

ModifyCacheSubnetGroup

CreateSnapshot

DeleteCacheParameterGroup

DescribeCacheSecurityGroups (Paginated)

ModifyCacheCluster

DescribeCacheEngineVersions (Paginated)

CreateCacheParameterGroup

DescribeReservedCacheNodes (Paginated)

DeleteCacheSubnetGroup

Types

AZMode

data AZMode Source #

Constructors

CrossAz 
SingleAz 

Instances

Bounded AZMode Source # 
Enum AZMode Source # 
Eq AZMode Source # 

Methods

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

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

Data AZMode Source # 

Methods

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

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

toConstr :: AZMode -> Constr #

dataTypeOf :: AZMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AZMode Source # 
Read AZMode Source # 
Show AZMode Source # 
Generic AZMode Source # 

Associated Types

type Rep AZMode :: * -> * #

Methods

from :: AZMode -> Rep AZMode x #

to :: Rep AZMode x -> AZMode #

Hashable AZMode Source # 

Methods

hashWithSalt :: Int -> AZMode -> Int #

hash :: AZMode -> Int #

NFData AZMode Source # 

Methods

rnf :: AZMode -> () #

ToQuery AZMode Source # 
ToHeader AZMode Source # 

Methods

toHeader :: HeaderName -> AZMode -> [Header] #

ToByteString AZMode Source # 

Methods

toBS :: AZMode -> ByteString #

FromText AZMode Source # 

Methods

parser :: Parser AZMode #

ToText AZMode Source # 

Methods

toText :: AZMode -> Text #

type Rep AZMode Source # 
type Rep AZMode = D1 (MetaData "AZMode" "Network.AWS.ElastiCache.Types.Sum" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) ((:+:) (C1 (MetaCons "CrossAz" PrefixI False) U1) (C1 (MetaCons "SingleAz" PrefixI False) U1))

AutomaticFailoverStatus

data AutomaticFailoverStatus Source #

Instances

Bounded AutomaticFailoverStatus Source # 
Enum AutomaticFailoverStatus Source # 
Eq AutomaticFailoverStatus Source # 
Data AutomaticFailoverStatus Source # 

Methods

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

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

toConstr :: AutomaticFailoverStatus -> Constr #

dataTypeOf :: AutomaticFailoverStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: AutomaticFailoverStatus -> () #

FromXML AutomaticFailoverStatus Source # 
ToQuery AutomaticFailoverStatus Source # 
ToHeader AutomaticFailoverStatus Source # 
ToByteString AutomaticFailoverStatus Source # 
FromText AutomaticFailoverStatus Source # 
ToText AutomaticFailoverStatus Source # 
type Rep AutomaticFailoverStatus Source # 
type Rep AutomaticFailoverStatus = D1 (MetaData "AutomaticFailoverStatus" "Network.AWS.ElastiCache.Types.Sum" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) ((:+:) ((:+:) (C1 (MetaCons "AFSDisabled" PrefixI False) U1) (C1 (MetaCons "AFSDisabling" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AFSEnabled" PrefixI False) U1) (C1 (MetaCons "AFSEnabling" PrefixI False) U1)))

ChangeType

data ChangeType Source #

Constructors

Immediate 
RequiresReboot 

Instances

Bounded ChangeType Source # 
Enum ChangeType Source # 
Eq ChangeType Source # 
Data ChangeType Source # 

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 # 
Read ChangeType Source # 
Show ChangeType Source # 
Generic ChangeType Source # 

Associated Types

type Rep ChangeType :: * -> * #

Hashable ChangeType Source # 
NFData ChangeType Source # 

Methods

rnf :: ChangeType -> () #

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

Methods

toText :: ChangeType -> Text #

type Rep ChangeType Source # 
type Rep ChangeType = D1 (MetaData "ChangeType" "Network.AWS.ElastiCache.Types.Sum" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) ((:+:) (C1 (MetaCons "Immediate" PrefixI False) U1) (C1 (MetaCons "RequiresReboot" PrefixI False) U1))

PendingAutomaticFailoverStatus

data PendingAutomaticFailoverStatus Source #

Constructors

Disabled 
Enabled 

Instances

Bounded PendingAutomaticFailoverStatus Source # 
Enum PendingAutomaticFailoverStatus Source # 
Eq PendingAutomaticFailoverStatus Source # 
Data PendingAutomaticFailoverStatus Source # 

Methods

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

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

toConstr :: PendingAutomaticFailoverStatus -> Constr #

dataTypeOf :: PendingAutomaticFailoverStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PendingAutomaticFailoverStatus Source # 
Read PendingAutomaticFailoverStatus Source # 
Show PendingAutomaticFailoverStatus Source # 
Generic PendingAutomaticFailoverStatus Source # 
Hashable PendingAutomaticFailoverStatus Source # 
NFData PendingAutomaticFailoverStatus Source # 
FromXML PendingAutomaticFailoverStatus Source # 
ToQuery PendingAutomaticFailoverStatus Source # 
ToHeader PendingAutomaticFailoverStatus Source # 
ToByteString PendingAutomaticFailoverStatus Source # 
FromText PendingAutomaticFailoverStatus Source # 
ToText PendingAutomaticFailoverStatus Source # 
type Rep PendingAutomaticFailoverStatus Source # 
type Rep PendingAutomaticFailoverStatus = D1 (MetaData "PendingAutomaticFailoverStatus" "Network.AWS.ElastiCache.Types.Sum" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) ((:+:) (C1 (MetaCons "Disabled" PrefixI False) U1) (C1 (MetaCons "Enabled" PrefixI False) U1))

SourceType

data SourceType Source #

Instances

Bounded SourceType Source # 
Enum SourceType Source # 
Eq SourceType Source # 
Data SourceType Source # 

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 # 
Read SourceType Source # 
Show SourceType Source # 
Generic SourceType Source # 

Associated Types

type Rep SourceType :: * -> * #

Hashable SourceType Source # 
NFData SourceType Source # 

Methods

rnf :: SourceType -> () #

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

Methods

toText :: SourceType -> Text #

type Rep SourceType Source # 
type Rep SourceType = D1 (MetaData "SourceType" "Network.AWS.ElastiCache.Types.Sum" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) ((:+:) ((:+:) (C1 (MetaCons "CacheCluster" PrefixI False) U1) (C1 (MetaCons "CacheParameterGroup" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CacheSecurityGroup" PrefixI False) U1) ((:+:) (C1 (MetaCons "CacheSubnetGroup" PrefixI False) U1) (C1 (MetaCons "ReplicationGroup" PrefixI False) U1))))

AvailabilityZone

data AvailabilityZone Source #

Describes an Availability Zone in which the cluster is launched.

See: availabilityZone smart constructor.

Instances

Eq AvailabilityZone Source # 
Data AvailabilityZone Source # 

Methods

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

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

toConstr :: AvailabilityZone -> Constr #

dataTypeOf :: AvailabilityZone -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AvailabilityZone Source # 
Show AvailabilityZone Source # 
Generic AvailabilityZone Source # 
Hashable AvailabilityZone Source # 
NFData AvailabilityZone Source # 

Methods

rnf :: AvailabilityZone -> () #

FromXML AvailabilityZone Source # 
type Rep AvailabilityZone Source # 
type Rep AvailabilityZone = D1 (MetaData "AvailabilityZone" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" True) (C1 (MetaCons "AvailabilityZone'" PrefixI True) (S1 (MetaSel (Just Symbol "_azName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

availabilityZone :: AvailabilityZone Source #

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

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

  • azName - The name of the Availability Zone.

azName :: Lens' AvailabilityZone (Maybe Text) Source #

The name of the Availability Zone.

CacheCluster

data CacheCluster Source #

Contains all of the attributes of a specific cluster.

See: cacheCluster smart constructor.

Instances

Eq CacheCluster Source # 
Data CacheCluster Source # 

Methods

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

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

toConstr :: CacheCluster -> Constr #

dataTypeOf :: CacheCluster -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheCluster Source # 
Show CacheCluster Source # 
Generic CacheCluster Source # 

Associated Types

type Rep CacheCluster :: * -> * #

Hashable CacheCluster Source # 
NFData CacheCluster Source # 

Methods

rnf :: CacheCluster -> () #

FromXML CacheCluster Source # 
type Rep CacheCluster Source # 
type Rep CacheCluster = D1 (MetaData "CacheCluster" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheCluster'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ccEngineVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ccCacheNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ccCacheNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CacheNode]))))) ((:*:) (S1 (MetaSel (Just Symbol "_ccCacheClusterCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))) ((:*:) (S1 (MetaSel (Just Symbol "_ccAtRestEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ccAutoMinorVersionUpgrade") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ccSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SecurityGroupMembership]))) ((:*:) (S1 (MetaSel (Just Symbol "_ccNotificationConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NotificationConfiguration))) (S1 (MetaSel (Just Symbol "_ccTransitEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_ccSnapshotWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ccCacheClusterId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ccConfigurationEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Endpoint))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ccEngine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ccCacheSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CacheSecurityGroupMembership]))) (S1 (MetaSel (Just Symbol "_ccAuthTokenEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_ccClientDownloadLandingPage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ccPreferredMaintenanceWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ccCacheSubnetGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ccPreferredAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ccCacheParameterGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CacheParameterGroupStatus))) (S1 (MetaSel (Just Symbol "_ccCacheClusterStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ccSnapshotRetentionLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_ccReplicationGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ccPendingModifiedValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PendingModifiedValues))) (S1 (MetaSel (Just Symbol "_ccNumCacheNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))))))

cacheCluster :: CacheCluster Source #

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

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

  • ccEngineVersion - The version of the cache engine that is used in this cluster.
  • ccCacheNodeType - The name of the compute and memory capacity node type for the cluster. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .
  • ccCacheNodes - A list of cache nodes that are members of the cluster.
  • ccCacheClusterCreateTime - The date and time when the cluster was created.
  • ccAtRestEncryptionEnabled - A flag that enables encryption at-rest when set to true . You cannot modify the value of AtRestEncryptionEnabled after the cluster is created. To enable at-rest encryption on a cluster you must set AtRestEncryptionEnabled to true when you create a cluster. Default: false
  • ccAutoMinorVersionUpgrade - This parameter is currently disabled.
  • ccSecurityGroups - A list of VPC Security Groups associated with the cluster.
  • ccNotificationConfiguration - Describes a notification topic and its status. Notification topics are used for publishing ElastiCache events to subscribers using Amazon Simple Notification Service (SNS).
  • ccTransitEncryptionEnabled - A flag that enables in-transit encryption when set to true . You cannot modify the value of TransitEncryptionEnabled after the cluster is created. To enable in-transit encryption on a cluster you must set TransitEncryptionEnabled to true when you create a cluster. Default: false
  • ccSnapshotWindow - The daily time range (in UTC) during which ElastiCache begins taking a daily snapshot of your cluster. Example: 05:00-09:00
  • ccCacheClusterId - The user-supplied identifier of the cluster. This identifier is a unique key that identifies a cluster.
  • ccConfigurationEndpoint - Represents a Memcached cluster endpoint which, if Automatic Discovery is enabled on the cluster, can be used by an application to connect to any node in the cluster. The configuration endpoint will always have .cfg in it. Example: mem-3.9dvc4r.cfg .usw2.cache.amazonaws.com:11211
  • ccEngine - The name of the cache engine (memcached or redis ) to be used for this cluster.
  • ccCacheSecurityGroups - A list of cache security group elements, composed of name and status sub-elements.
  • ccAuthTokenEnabled - A flag that enables using an AuthToken (password) when issuing Redis commands. Default: false
  • ccClientDownloadLandingPage - The URL of the web page where you can download the latest ElastiCache client library.
  • ccPreferredMaintenanceWindow - Specifies the weekly time range during which maintenance on the cluster is performed. It is specified as a range in the format ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window is a 60 minute period. Valid values for ddd are: * sun * mon * tue * wed * thu * fri * sat Example: sun:23:00-mon:01:30
  • ccCacheSubnetGroupName - The name of the cache subnet group associated with the cluster.
  • ccPreferredAvailabilityZone - The name of the Availability Zone in which the cluster is located or Multiple if the cache nodes are located in different Availability Zones.
  • ccCacheParameterGroup - Status of the cache parameter group.
  • ccCacheClusterStatus - The current state of this cluster, one of the following values: available , creating , deleted , deleting , incompatible-network , modifying , rebooting cluster nodes , restore-failed , or snapshotting .
  • ccSnapshotRetentionLimit - The number of days for which ElastiCache retains automatic cluster snapshots before deleting them. For example, if you set SnapshotRetentionLimit to 5, a snapshot that was taken today is retained for 5 days before being deleted. Important: If the value of SnapshotRetentionLimit is set to zero (0), backups are turned off.
  • ccReplicationGroupId - The replication group to which this cluster belongs. If this field is empty, the cluster is not associated with any replication group.
  • ccPendingModifiedValues - Undocumented member.
  • ccNumCacheNodes - The number of cache nodes in the cluster. For clusters running Redis, this value must be 1. For clusters running Memcached, this value must be between 1 and 20.

ccEngineVersion :: Lens' CacheCluster (Maybe Text) Source #

The version of the cache engine that is used in this cluster.

ccCacheNodeType :: Lens' CacheCluster (Maybe Text) Source #

The name of the compute and memory capacity node type for the cluster. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .

ccCacheNodes :: Lens' CacheCluster [CacheNode] Source #

A list of cache nodes that are members of the cluster.

ccCacheClusterCreateTime :: Lens' CacheCluster (Maybe UTCTime) Source #

The date and time when the cluster was created.

ccAtRestEncryptionEnabled :: Lens' CacheCluster (Maybe Bool) Source #

A flag that enables encryption at-rest when set to true . You cannot modify the value of AtRestEncryptionEnabled after the cluster is created. To enable at-rest encryption on a cluster you must set AtRestEncryptionEnabled to true when you create a cluster. Default: false

ccAutoMinorVersionUpgrade :: Lens' CacheCluster (Maybe Bool) Source #

This parameter is currently disabled.

ccSecurityGroups :: Lens' CacheCluster [SecurityGroupMembership] Source #

A list of VPC Security Groups associated with the cluster.

ccNotificationConfiguration :: Lens' CacheCluster (Maybe NotificationConfiguration) Source #

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

ccTransitEncryptionEnabled :: Lens' CacheCluster (Maybe Bool) Source #

A flag that enables in-transit encryption when set to true . You cannot modify the value of TransitEncryptionEnabled after the cluster is created. To enable in-transit encryption on a cluster you must set TransitEncryptionEnabled to true when you create a cluster. Default: false

ccSnapshotWindow :: Lens' CacheCluster (Maybe Text) Source #

The daily time range (in UTC) during which ElastiCache begins taking a daily snapshot of your cluster. Example: 05:00-09:00

ccCacheClusterId :: Lens' CacheCluster (Maybe Text) Source #

The user-supplied identifier of the cluster. This identifier is a unique key that identifies a cluster.

ccConfigurationEndpoint :: Lens' CacheCluster (Maybe Endpoint) Source #

Represents a Memcached cluster endpoint which, if Automatic Discovery is enabled on the cluster, can be used by an application to connect to any node in the cluster. The configuration endpoint will always have .cfg in it. Example: mem-3.9dvc4r.cfg .usw2.cache.amazonaws.com:11211

ccEngine :: Lens' CacheCluster (Maybe Text) Source #

The name of the cache engine (memcached or redis ) to be used for this cluster.

ccCacheSecurityGroups :: Lens' CacheCluster [CacheSecurityGroupMembership] Source #

A list of cache security group elements, composed of name and status sub-elements.

ccAuthTokenEnabled :: Lens' CacheCluster (Maybe Bool) Source #

A flag that enables using an AuthToken (password) when issuing Redis commands. Default: false

ccClientDownloadLandingPage :: Lens' CacheCluster (Maybe Text) Source #

The URL of the web page where you can download the latest ElastiCache client library.

ccPreferredMaintenanceWindow :: Lens' CacheCluster (Maybe Text) Source #

Specifies the weekly time range during which maintenance on the cluster is performed. It is specified as a range in the format ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window is a 60 minute period. Valid values for ddd are: * sun * mon * tue * wed * thu * fri * sat Example: sun:23:00-mon:01:30

ccCacheSubnetGroupName :: Lens' CacheCluster (Maybe Text) Source #

The name of the cache subnet group associated with the cluster.

ccPreferredAvailabilityZone :: Lens' CacheCluster (Maybe Text) Source #

The name of the Availability Zone in which the cluster is located or Multiple if the cache nodes are located in different Availability Zones.

ccCacheClusterStatus :: Lens' CacheCluster (Maybe Text) Source #

The current state of this cluster, one of the following values: available , creating , deleted , deleting , incompatible-network , modifying , rebooting cluster nodes , restore-failed , or snapshotting .

ccSnapshotRetentionLimit :: Lens' CacheCluster (Maybe Int) Source #

The number of days for which ElastiCache retains automatic cluster snapshots before deleting them. For example, if you set SnapshotRetentionLimit to 5, a snapshot that was taken today is retained for 5 days before being deleted. Important: If the value of SnapshotRetentionLimit is set to zero (0), backups are turned off.

ccReplicationGroupId :: Lens' CacheCluster (Maybe Text) Source #

The replication group to which this cluster belongs. If this field is empty, the cluster is not associated with any replication group.

ccNumCacheNodes :: Lens' CacheCluster (Maybe Int) Source #

The number of cache nodes in the cluster. For clusters running Redis, this value must be 1. For clusters running Memcached, this value must be between 1 and 20.

CacheEngineVersion

data CacheEngineVersion Source #

Provides all of the details about a particular cache engine version.

See: cacheEngineVersion smart constructor.

Instances

Eq CacheEngineVersion Source # 
Data CacheEngineVersion Source # 

Methods

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

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

toConstr :: CacheEngineVersion -> Constr #

dataTypeOf :: CacheEngineVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheEngineVersion Source # 
Show CacheEngineVersion Source # 
Generic CacheEngineVersion Source # 
Hashable CacheEngineVersion Source # 
NFData CacheEngineVersion Source # 

Methods

rnf :: CacheEngineVersion -> () #

FromXML CacheEngineVersion Source # 
type Rep CacheEngineVersion Source # 
type Rep CacheEngineVersion = D1 (MetaData "CacheEngineVersion" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheEngineVersion'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cevEngineVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cevCacheParameterGroupFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cevCacheEngineDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cevEngine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cevCacheEngineVersionDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

cacheEngineVersion :: CacheEngineVersion Source #

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

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

cevEngineVersion :: Lens' CacheEngineVersion (Maybe Text) Source #

The version number of the cache engine.

cevCacheParameterGroupFamily :: Lens' CacheEngineVersion (Maybe Text) Source #

The name of the cache parameter group family associated with this cache engine. Valid values are: memcached1.4 | redis2.6 | redis2.8 | redis3.2

cevCacheEngineDescription :: Lens' CacheEngineVersion (Maybe Text) Source #

The description of the cache engine.

cevEngine :: Lens' CacheEngineVersion (Maybe Text) Source #

The name of the cache engine.

cevCacheEngineVersionDescription :: Lens' CacheEngineVersion (Maybe Text) Source #

The description of the cache engine version.

CacheNode

data CacheNode Source #

Represents an individual cache node within a cluster. Each cache node runs its own instance of the cluster's protocol-compliant caching software - either Memcached or Redis.

The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts.

  • General purpose:
  • Current generation:

T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium

M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge

M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge

  • Previous generation: (not recommended)

T1 node types: cache.t1.micro

M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge

  • Compute optimized:
  • Previous generation: (not recommended)

C1 node types: cache.c1.xlarge

  • Memory optimized:
  • Current generation:

R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge

  • Previous generation: (not recommended)

M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge

Notes:

  • All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC).
  • Redis (cluster mode disabled): Redis backup/restore is not supported on T1 and T2 instances.
  • Redis (cluster mode enabled): Backup/restore is not supported on T1 instances.
  • Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances.

For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .

See: cacheNode smart constructor.

Instances

Eq CacheNode Source # 
Data CacheNode Source # 

Methods

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

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

toConstr :: CacheNode -> Constr #

dataTypeOf :: CacheNode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheNode Source # 
Show CacheNode Source # 
Generic CacheNode Source # 

Associated Types

type Rep CacheNode :: * -> * #

Hashable CacheNode Source # 
NFData CacheNode Source # 

Methods

rnf :: CacheNode -> () #

FromXML CacheNode Source # 
type Rep CacheNode Source # 
type Rep CacheNode = D1 (MetaData "CacheNode" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheNode'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cnSourceCacheNodeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cnParameterGroupStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cnCacheNodeCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cnCustomerAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cnCacheNodeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cnCacheNodeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cnEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Endpoint)))))))

cacheNode :: CacheNode Source #

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

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

  • cnSourceCacheNodeId - The ID of the primary node to which this read replica node is synchronized. If this field is empty, this node is not associated with a primary cluster.
  • cnParameterGroupStatus - The status of the parameter group applied to this cache node.
  • cnCacheNodeCreateTime - The date and time when the cache node was created.
  • cnCustomerAvailabilityZone - The Availability Zone where this node was created and now resides.
  • cnCacheNodeId - The cache node identifier. A node ID is a numeric identifier (0001, 0002, etc.). The combination of cluster ID and node ID uniquely identifies every cache node used in a customer's AWS account.
  • cnCacheNodeStatus - The current state of this cache node.
  • cnEndpoint - The hostname for connecting to this cache node.

cnSourceCacheNodeId :: Lens' CacheNode (Maybe Text) Source #

The ID of the primary node to which this read replica node is synchronized. If this field is empty, this node is not associated with a primary cluster.

cnParameterGroupStatus :: Lens' CacheNode (Maybe Text) Source #

The status of the parameter group applied to this cache node.

cnCacheNodeCreateTime :: Lens' CacheNode (Maybe UTCTime) Source #

The date and time when the cache node was created.

cnCustomerAvailabilityZone :: Lens' CacheNode (Maybe Text) Source #

The Availability Zone where this node was created and now resides.

cnCacheNodeId :: Lens' CacheNode (Maybe Text) Source #

The cache node identifier. A node ID is a numeric identifier (0001, 0002, etc.). The combination of cluster ID and node ID uniquely identifies every cache node used in a customer's AWS account.

cnCacheNodeStatus :: Lens' CacheNode (Maybe Text) Source #

The current state of this cache node.

cnEndpoint :: Lens' CacheNode (Maybe Endpoint) Source #

The hostname for connecting to this cache node.

CacheNodeTypeSpecificParameter

data CacheNodeTypeSpecificParameter Source #

A parameter that has a different value for each cache node type it is applied to. For example, in a Redis cluster, a cache.m1.large cache node type would have a larger maxmemory value than a cache.m1.small type.

See: cacheNodeTypeSpecificParameter smart constructor.

Instances

Eq CacheNodeTypeSpecificParameter Source # 
Data CacheNodeTypeSpecificParameter Source # 

Methods

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

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

toConstr :: CacheNodeTypeSpecificParameter -> Constr #

dataTypeOf :: CacheNodeTypeSpecificParameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheNodeTypeSpecificParameter Source # 
Show CacheNodeTypeSpecificParameter Source # 
Generic CacheNodeTypeSpecificParameter Source # 
Hashable CacheNodeTypeSpecificParameter Source # 
NFData CacheNodeTypeSpecificParameter Source # 
FromXML CacheNodeTypeSpecificParameter Source # 
type Rep CacheNodeTypeSpecificParameter Source # 
type Rep CacheNodeTypeSpecificParameter = D1 (MetaData "CacheNodeTypeSpecificParameter" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheNodeTypeSpecificParameter'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cntspCacheNodeTypeSpecificValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CacheNodeTypeSpecificValue]))) (S1 (MetaSel (Just Symbol "_cntspMinimumEngineVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cntspSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cntspIsModifiable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cntspDataType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cntspAllowedValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cntspParameterName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cntspDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cntspChangeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChangeType))))))))

cacheNodeTypeSpecificParameter :: CacheNodeTypeSpecificParameter Source #

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

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

cntspCacheNodeTypeSpecificValues :: Lens' CacheNodeTypeSpecificParameter [CacheNodeTypeSpecificValue] Source #

A list of cache node types and their corresponding values for this parameter.

cntspMinimumEngineVersion :: Lens' CacheNodeTypeSpecificParameter (Maybe Text) Source #

The earliest cache engine version to which the parameter can apply.

cntspSource :: Lens' CacheNodeTypeSpecificParameter (Maybe Text) Source #

The source of the parameter value.

cntspIsModifiable :: Lens' CacheNodeTypeSpecificParameter (Maybe Bool) Source #

Indicates whether (true ) or not (false ) the parameter can be modified. Some parameters have security or operational implications that prevent them from being changed.

cntspDataType :: Lens' CacheNodeTypeSpecificParameter (Maybe Text) Source #

The valid data type for the parameter.

cntspAllowedValues :: Lens' CacheNodeTypeSpecificParameter (Maybe Text) Source #

The valid range of values for the parameter.

cntspChangeType :: Lens' CacheNodeTypeSpecificParameter (Maybe ChangeType) Source #

Indicates whether a change to the parameter is applied immediately or requires a reboot for the change to be applied. You can force a reboot or wait until the next maintenance window's reboot. For more information, see Rebooting a Cluster .

CacheNodeTypeSpecificValue

data CacheNodeTypeSpecificValue Source #

A value that applies only to a certain cache node type.

See: cacheNodeTypeSpecificValue smart constructor.

Instances

Eq CacheNodeTypeSpecificValue Source # 
Data CacheNodeTypeSpecificValue Source # 

Methods

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

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

toConstr :: CacheNodeTypeSpecificValue -> Constr #

dataTypeOf :: CacheNodeTypeSpecificValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheNodeTypeSpecificValue Source # 
Show CacheNodeTypeSpecificValue Source # 
Generic CacheNodeTypeSpecificValue Source # 
Hashable CacheNodeTypeSpecificValue Source # 
NFData CacheNodeTypeSpecificValue Source # 
FromXML CacheNodeTypeSpecificValue Source # 
type Rep CacheNodeTypeSpecificValue Source # 
type Rep CacheNodeTypeSpecificValue = D1 (MetaData "CacheNodeTypeSpecificValue" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheNodeTypeSpecificValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cntsvCacheNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cntsvValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

cacheNodeTypeSpecificValue :: CacheNodeTypeSpecificValue Source #

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

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

cntsvCacheNodeType :: Lens' CacheNodeTypeSpecificValue (Maybe Text) Source #

The cache node type for which this value applies.

cntsvValue :: Lens' CacheNodeTypeSpecificValue (Maybe Text) Source #

The value for the cache node type.

CacheParameterGroup

data CacheParameterGroup Source #

Represents the output of a CreateCacheParameterGroup operation.

See: cacheParameterGroup smart constructor.

Instances

Eq CacheParameterGroup Source # 
Data CacheParameterGroup Source # 

Methods

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

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

toConstr :: CacheParameterGroup -> Constr #

dataTypeOf :: CacheParameterGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheParameterGroup Source # 
Show CacheParameterGroup Source # 
Generic CacheParameterGroup Source # 
Hashable CacheParameterGroup Source # 
NFData CacheParameterGroup Source # 

Methods

rnf :: CacheParameterGroup -> () #

FromXML CacheParameterGroup Source # 
type Rep CacheParameterGroup Source # 
type Rep CacheParameterGroup = D1 (MetaData "CacheParameterGroup" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheParameterGroup'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cpgCacheParameterGroupFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cpgCacheParameterGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cpgDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

cacheParameterGroup :: CacheParameterGroup Source #

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

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

cpgCacheParameterGroupFamily :: Lens' CacheParameterGroup (Maybe Text) Source #

The name of the cache parameter group family that this cache parameter group is compatible with. Valid values are: memcached1.4 | redis2.6 | redis2.8 | redis3.2

cpgCacheParameterGroupName :: Lens' CacheParameterGroup (Maybe Text) Source #

The name of the cache parameter group.

cpgDescription :: Lens' CacheParameterGroup (Maybe Text) Source #

The description for this cache parameter group.

CacheParameterGroupNameMessage

data CacheParameterGroupNameMessage Source #

Represents the output of one of the following operations:

  • ModifyCacheParameterGroup
  • ResetCacheParameterGroup

See: cacheParameterGroupNameMessage smart constructor.

Instances

Eq CacheParameterGroupNameMessage Source # 
Data CacheParameterGroupNameMessage Source # 

Methods

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

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

toConstr :: CacheParameterGroupNameMessage -> Constr #

dataTypeOf :: CacheParameterGroupNameMessage -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheParameterGroupNameMessage Source # 
Show CacheParameterGroupNameMessage Source # 
Generic CacheParameterGroupNameMessage Source # 
Hashable CacheParameterGroupNameMessage Source # 
NFData CacheParameterGroupNameMessage Source # 
FromXML CacheParameterGroupNameMessage Source # 
type Rep CacheParameterGroupNameMessage Source # 
type Rep CacheParameterGroupNameMessage = D1 (MetaData "CacheParameterGroupNameMessage" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" True) (C1 (MetaCons "CacheParameterGroupNameMessage'" PrefixI True) (S1 (MetaSel (Just Symbol "_cpgnmCacheParameterGroupName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

cacheParameterGroupNameMessage :: CacheParameterGroupNameMessage Source #

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

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

CacheParameterGroupStatus

data CacheParameterGroupStatus Source #

Status of the cache parameter group.

See: cacheParameterGroupStatus smart constructor.

Instances

Eq CacheParameterGroupStatus Source # 
Data CacheParameterGroupStatus Source # 

Methods

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

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

toConstr :: CacheParameterGroupStatus -> Constr #

dataTypeOf :: CacheParameterGroupStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheParameterGroupStatus Source # 
Show CacheParameterGroupStatus Source # 
Generic CacheParameterGroupStatus Source # 
Hashable CacheParameterGroupStatus Source # 
NFData CacheParameterGroupStatus Source # 
FromXML CacheParameterGroupStatus Source # 
type Rep CacheParameterGroupStatus Source # 
type Rep CacheParameterGroupStatus = D1 (MetaData "CacheParameterGroupStatus" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheParameterGroupStatus'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cpgsCacheParameterGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cpgsCacheNodeIdsToReboot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_cpgsParameterApplyStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

cacheParameterGroupStatus :: CacheParameterGroupStatus Source #

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

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

cpgsCacheParameterGroupName :: Lens' CacheParameterGroupStatus (Maybe Text) Source #

The name of the cache parameter group.

cpgsCacheNodeIdsToReboot :: Lens' CacheParameterGroupStatus [Text] Source #

A list of the cache node IDs which need to be rebooted for parameter changes to be applied. A node ID is a numeric identifier (0001, 0002, etc.).

CacheSecurityGroup

data CacheSecurityGroup Source #

Represents the output of one of the following operations:

  • AuthorizeCacheSecurityGroupIngress
  • CreateCacheSecurityGroup
  • RevokeCacheSecurityGroupIngress

See: cacheSecurityGroup smart constructor.

Instances

Eq CacheSecurityGroup Source # 
Data CacheSecurityGroup Source # 

Methods

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

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

toConstr :: CacheSecurityGroup -> Constr #

dataTypeOf :: CacheSecurityGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheSecurityGroup Source # 
Show CacheSecurityGroup Source # 
Generic CacheSecurityGroup Source # 
Hashable CacheSecurityGroup Source # 
NFData CacheSecurityGroup Source # 

Methods

rnf :: CacheSecurityGroup -> () #

FromXML CacheSecurityGroup Source # 
type Rep CacheSecurityGroup Source # 
type Rep CacheSecurityGroup = D1 (MetaData "CacheSecurityGroup" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheSecurityGroup'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_csgCacheSecurityGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_csgOwnerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_csgEC2SecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [EC2SecurityGroup]))) (S1 (MetaSel (Just Symbol "_csgDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

cacheSecurityGroup :: CacheSecurityGroup Source #

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

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

csgCacheSecurityGroupName :: Lens' CacheSecurityGroup (Maybe Text) Source #

The name of the cache security group.

csgOwnerId :: Lens' CacheSecurityGroup (Maybe Text) Source #

The AWS account ID of the cache security group owner.

csgEC2SecurityGroups :: Lens' CacheSecurityGroup [EC2SecurityGroup] Source #

A list of Amazon EC2 security groups that are associated with this cache security group.

csgDescription :: Lens' CacheSecurityGroup (Maybe Text) Source #

The description of the cache security group.

CacheSecurityGroupMembership

data CacheSecurityGroupMembership Source #

Represents a cluster's status within a particular cache security group.

See: cacheSecurityGroupMembership smart constructor.

Instances

Eq CacheSecurityGroupMembership Source # 
Data CacheSecurityGroupMembership Source # 

Methods

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

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

toConstr :: CacheSecurityGroupMembership -> Constr #

dataTypeOf :: CacheSecurityGroupMembership -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheSecurityGroupMembership Source # 
Show CacheSecurityGroupMembership Source # 
Generic CacheSecurityGroupMembership Source # 
Hashable CacheSecurityGroupMembership Source # 
NFData CacheSecurityGroupMembership Source # 
FromXML CacheSecurityGroupMembership Source # 
type Rep CacheSecurityGroupMembership Source # 
type Rep CacheSecurityGroupMembership = D1 (MetaData "CacheSecurityGroupMembership" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheSecurityGroupMembership'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_csgmStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_csgmCacheSecurityGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

cacheSecurityGroupMembership :: CacheSecurityGroupMembership Source #

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

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

  • csgmStatus - The membership status in the cache security group. The status changes when a cache security group is modified, or when the cache security groups assigned to a cluster are modified.
  • csgmCacheSecurityGroupName - The name of the cache security group.

csgmStatus :: Lens' CacheSecurityGroupMembership (Maybe Text) Source #

The membership status in the cache security group. The status changes when a cache security group is modified, or when the cache security groups assigned to a cluster are modified.

CacheSubnetGroup

data CacheSubnetGroup Source #

Represents the output of one of the following operations:

  • CreateCacheSubnetGroup
  • ModifyCacheSubnetGroup

See: cacheSubnetGroup smart constructor.

Instances

Eq CacheSubnetGroup Source # 
Data CacheSubnetGroup Source # 

Methods

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

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

toConstr :: CacheSubnetGroup -> Constr #

dataTypeOf :: CacheSubnetGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CacheSubnetGroup Source # 
Show CacheSubnetGroup Source # 
Generic CacheSubnetGroup Source # 
Hashable CacheSubnetGroup Source # 
NFData CacheSubnetGroup Source # 

Methods

rnf :: CacheSubnetGroup -> () #

FromXML CacheSubnetGroup Source # 
type Rep CacheSubnetGroup Source # 
type Rep CacheSubnetGroup = D1 (MetaData "CacheSubnetGroup" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "CacheSubnetGroup'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_csgVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_csgSubnets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Subnet])))) ((:*:) (S1 (MetaSel (Just Symbol "_csgCacheSubnetGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_csgCacheSubnetGroupDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

cacheSubnetGroup :: CacheSubnetGroup Source #

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

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

csgVPCId :: Lens' CacheSubnetGroup (Maybe Text) Source #

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

csgSubnets :: Lens' CacheSubnetGroup [Subnet] Source #

A list of subnets associated with the cache subnet group.

csgCacheSubnetGroupName :: Lens' CacheSubnetGroup (Maybe Text) Source #

The name of the cache subnet group.

csgCacheSubnetGroupDescription :: Lens' CacheSubnetGroup (Maybe Text) Source #

The description of the cache subnet group.

EC2SecurityGroup

data EC2SecurityGroup Source #

Provides ownership and status information for an Amazon EC2 security group.

See: ec2SecurityGroup smart constructor.

Instances

Eq EC2SecurityGroup Source # 
Data EC2SecurityGroup Source # 

Methods

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

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

toConstr :: EC2SecurityGroup -> Constr #

dataTypeOf :: EC2SecurityGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EC2SecurityGroup Source # 
Show EC2SecurityGroup Source # 
Generic EC2SecurityGroup Source # 
Hashable EC2SecurityGroup Source # 
NFData EC2SecurityGroup Source # 

Methods

rnf :: EC2SecurityGroup -> () #

FromXML EC2SecurityGroup Source # 
type Rep EC2SecurityGroup Source # 
type Rep EC2SecurityGroup = D1 (MetaData "EC2SecurityGroup" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "EC2SecurityGroup'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_esgStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_esgEC2SecurityGroupOwnerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_esgEC2SecurityGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

ec2SecurityGroup :: EC2SecurityGroup Source #

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

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

esgStatus :: Lens' EC2SecurityGroup (Maybe Text) Source #

The status of the Amazon EC2 security group.

esgEC2SecurityGroupOwnerId :: Lens' EC2SecurityGroup (Maybe Text) Source #

The AWS account ID of the Amazon EC2 security group owner.

esgEC2SecurityGroupName :: Lens' EC2SecurityGroup (Maybe Text) Source #

The name of the Amazon EC2 security group.

Endpoint

data Endpoint Source #

Represents the information required for client programs to connect to a cache node.

See: endpoint smart constructor.

Instances

Eq Endpoint Source # 
Data Endpoint Source # 

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 # 
Show Endpoint Source # 
Generic Endpoint Source # 

Associated Types

type Rep Endpoint :: * -> * #

Methods

from :: Endpoint -> Rep Endpoint x #

to :: Rep Endpoint x -> Endpoint #

Hashable Endpoint Source # 

Methods

hashWithSalt :: Int -> Endpoint -> Int #

hash :: Endpoint -> Int #

NFData Endpoint Source # 

Methods

rnf :: Endpoint -> () #

FromXML Endpoint Source # 
type Rep Endpoint Source # 
type Rep Endpoint = D1 (MetaData "Endpoint" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "Endpoint'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_eAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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 cache node.
  • ePort - The port number that the cache engine is listening on.

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

The DNS hostname of the cache node.

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

The port number that the cache engine is listening on.

EngineDefaults

data EngineDefaults Source #

Represents the output of a DescribeEngineDefaultParameters operation.

See: engineDefaults smart constructor.

Instances

Eq EngineDefaults Source # 
Data EngineDefaults Source # 

Methods

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

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

toConstr :: EngineDefaults -> Constr #

dataTypeOf :: EngineDefaults -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EngineDefaults Source # 
Show EngineDefaults Source # 
Generic EngineDefaults Source # 

Associated Types

type Rep EngineDefaults :: * -> * #

Hashable EngineDefaults Source # 
NFData EngineDefaults Source # 

Methods

rnf :: EngineDefaults -> () #

FromXML EngineDefaults Source # 
type Rep EngineDefaults Source # 
type Rep EngineDefaults = D1 (MetaData "EngineDefaults" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "EngineDefaults'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_edCacheParameterGroupFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_edCacheNodeTypeSpecificParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CacheNodeTypeSpecificParameter])))) ((:*:) (S1 (MetaSel (Just Symbol "_edMarker") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_edParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Parameter]))))))

engineDefaults :: EngineDefaults Source #

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

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

  • edCacheParameterGroupFamily - Specifies the name of the cache parameter group family to which the engine default parameters apply. Valid values are: memcached1.4 | redis2.6 | redis2.8 | redis3.2
  • edCacheNodeTypeSpecificParameters - A list of parameters specific to a particular cache node type. Each element in the list contains detailed information about one parameter.
  • edMarker - Provides an identifier to allow retrieval of paginated results.
  • edParameters - Contains a list of engine default parameters.

edCacheParameterGroupFamily :: Lens' EngineDefaults (Maybe Text) Source #

Specifies the name of the cache parameter group family to which the engine default parameters apply. Valid values are: memcached1.4 | redis2.6 | redis2.8 | redis3.2

edCacheNodeTypeSpecificParameters :: Lens' EngineDefaults [CacheNodeTypeSpecificParameter] Source #

A list of parameters specific to a particular cache node type. Each element in the list contains detailed information about one parameter.

edMarker :: Lens' EngineDefaults (Maybe Text) Source #

Provides an identifier to allow retrieval of paginated results.

edParameters :: Lens' EngineDefaults [Parameter] Source #

Contains a list of engine default parameters.

Event

data Event Source #

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

See: event smart constructor.

Instances

Eq Event Source # 

Methods

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

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

Data Event Source # 

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 # 
Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Hashable Event Source # 

Methods

hashWithSalt :: Int -> Event -> Int #

hash :: Event -> Int #

NFData Event Source # 

Methods

rnf :: Event -> () #

FromXML Event Source # 

Methods

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

type Rep Event Source # 
type Rep Event = D1 (MetaData "Event" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "Event'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eSourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SourceType))) (S1 (MetaSel (Just Symbol "_eSourceIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_eDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))) (S1 (MetaSel (Just Symbol "_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:

  • eSourceType - Specifies the origin of this event - a cluster, a parameter group, a security group, etc.
  • eSourceIdentifier - The identifier for the source of the event. For example, if the event occurred at the cluster level, the identifier would be the name of the cluster.
  • eDate - The date and time when the event occurred.
  • eMessage - The text of the event.

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

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

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

The identifier for the source of the event. For example, if the event occurred at the cluster level, the identifier would be the name of the cluster.

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

The date and time when the event occurred.

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

The text of the event.

NodeGroup

data NodeGroup Source #

Represents a collection of cache nodes in a replication group. One node in the node group is the read/write primary node. All the other nodes are read-only Replica nodes.

See: nodeGroup smart constructor.

Instances

Eq NodeGroup Source # 
Data NodeGroup Source # 

Methods

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

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

toConstr :: NodeGroup -> Constr #

dataTypeOf :: NodeGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NodeGroup Source # 
Show NodeGroup Source # 
Generic NodeGroup Source # 

Associated Types

type Rep NodeGroup :: * -> * #

Hashable NodeGroup Source # 
NFData NodeGroup Source # 

Methods

rnf :: NodeGroup -> () #

FromXML NodeGroup Source # 
type Rep NodeGroup Source # 
type Rep NodeGroup = D1 (MetaData "NodeGroup" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "NodeGroup'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ngStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ngPrimaryEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Endpoint)))) ((:*:) (S1 (MetaSel (Just Symbol "_ngSlots") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ngNodeGroupMembers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [NodeGroupMember]))) (S1 (MetaSel (Just Symbol "_ngNodeGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

nodeGroup :: NodeGroup Source #

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

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

  • ngStatus - The current state of this replication group - creating , available , etc.
  • ngPrimaryEndpoint - The endpoint of the primary node in this node group (shard).
  • ngSlots - The keyspace for this node group (shard).
  • ngNodeGroupMembers - A list containing information about individual nodes within the node group (shard).
  • ngNodeGroupId - The identifier for the node group (shard). A Redis (cluster mode disabled) replication group contains only 1 node group; therefore, the node group ID is 0001. A Redis (cluster mode enabled) replication group contains 1 to 15 node groups numbered 0001 to 0015.

ngStatus :: Lens' NodeGroup (Maybe Text) Source #

The current state of this replication group - creating , available , etc.

ngPrimaryEndpoint :: Lens' NodeGroup (Maybe Endpoint) Source #

The endpoint of the primary node in this node group (shard).

ngSlots :: Lens' NodeGroup (Maybe Text) Source #

The keyspace for this node group (shard).

ngNodeGroupMembers :: Lens' NodeGroup [NodeGroupMember] Source #

A list containing information about individual nodes within the node group (shard).

ngNodeGroupId :: Lens' NodeGroup (Maybe Text) Source #

The identifier for the node group (shard). A Redis (cluster mode disabled) replication group contains only 1 node group; therefore, the node group ID is 0001. A Redis (cluster mode enabled) replication group contains 1 to 15 node groups numbered 0001 to 0015.

NodeGroupConfiguration

data NodeGroupConfiguration Source #

Node group (shard) configuration options. Each node group (shard) configuration has the following: Slots , PrimaryAvailabilityZone , ReplicaAvailabilityZones , ReplicaCount .

See: nodeGroupConfiguration smart constructor.

Instances

Eq NodeGroupConfiguration Source # 
Data NodeGroupConfiguration Source # 

Methods

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

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

toConstr :: NodeGroupConfiguration -> Constr #

dataTypeOf :: NodeGroupConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NodeGroupConfiguration Source # 
Show NodeGroupConfiguration Source # 
Generic NodeGroupConfiguration Source # 
Hashable NodeGroupConfiguration Source # 
NFData NodeGroupConfiguration Source # 

Methods

rnf :: NodeGroupConfiguration -> () #

FromXML NodeGroupConfiguration Source # 
ToQuery NodeGroupConfiguration Source # 
type Rep NodeGroupConfiguration Source # 
type Rep NodeGroupConfiguration = D1 (MetaData "NodeGroupConfiguration" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "NodeGroupConfiguration'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ngcSlots") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ngcReplicaCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "_ngcPrimaryAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ngcReplicaAvailabilityZones") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))

nodeGroupConfiguration :: NodeGroupConfiguration Source #

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

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

  • ngcSlots - A string that specifies the keyspace for a particular node group. Keyspaces range from 0 to 16,383. The string is in the format startkey-endkey . Example: "0-3999"
  • ngcReplicaCount - The number of read replica nodes in this node group (shard).
  • ngcPrimaryAvailabilityZone - The Availability Zone where the primary node of this node group (shard) is launched.
  • ngcReplicaAvailabilityZones - A list of Availability Zones to be used for the read replicas. The number of Availability Zones in this list must match the value of ReplicaCount or ReplicasPerNodeGroup if not specified.

ngcSlots :: Lens' NodeGroupConfiguration (Maybe Text) Source #

A string that specifies the keyspace for a particular node group. Keyspaces range from 0 to 16,383. The string is in the format startkey-endkey . Example: "0-3999"

ngcReplicaCount :: Lens' NodeGroupConfiguration (Maybe Int) Source #

The number of read replica nodes in this node group (shard).

ngcPrimaryAvailabilityZone :: Lens' NodeGroupConfiguration (Maybe Text) Source #

The Availability Zone where the primary node of this node group (shard) is launched.

ngcReplicaAvailabilityZones :: Lens' NodeGroupConfiguration [Text] Source #

A list of Availability Zones to be used for the read replicas. The number of Availability Zones in this list must match the value of ReplicaCount or ReplicasPerNodeGroup if not specified.

NodeGroupMember

data NodeGroupMember Source #

Represents a single node within a node group (shard).

See: nodeGroupMember smart constructor.

Instances

Eq NodeGroupMember Source # 
Data NodeGroupMember Source # 

Methods

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

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

toConstr :: NodeGroupMember -> Constr #

dataTypeOf :: NodeGroupMember -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NodeGroupMember Source # 
Show NodeGroupMember Source # 
Generic NodeGroupMember Source # 
Hashable NodeGroupMember Source # 
NFData NodeGroupMember Source # 

Methods

rnf :: NodeGroupMember -> () #

FromXML NodeGroupMember Source # 
type Rep NodeGroupMember Source # 
type Rep NodeGroupMember = D1 (MetaData "NodeGroupMember" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "NodeGroupMember'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ngmCacheClusterId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ngmCacheNodeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ngmPreferredAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ngmCurrentRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ngmReadEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Endpoint)))))))

nodeGroupMember :: NodeGroupMember Source #

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

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

ngmCacheClusterId :: Lens' NodeGroupMember (Maybe Text) Source #

The ID of the cluster to which the node belongs.

ngmCacheNodeId :: Lens' NodeGroupMember (Maybe Text) Source #

The ID of the node within its cluster. A node ID is a numeric identifier (0001, 0002, etc.).

ngmPreferredAvailabilityZone :: Lens' NodeGroupMember (Maybe Text) Source #

The name of the Availability Zone in which the node is located.

ngmCurrentRole :: Lens' NodeGroupMember (Maybe Text) Source #

The role that is currently assigned to the node - primary or replica .

NodeSnapshot

data NodeSnapshot Source #

Represents an individual cache node in a snapshot of a cluster.

See: nodeSnapshot smart constructor.

Instances

Eq NodeSnapshot Source # 
Data NodeSnapshot Source # 

Methods

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

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

toConstr :: NodeSnapshot -> Constr #

dataTypeOf :: NodeSnapshot -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NodeSnapshot Source # 
Show NodeSnapshot Source # 
Generic NodeSnapshot Source # 

Associated Types

type Rep NodeSnapshot :: * -> * #

Hashable NodeSnapshot Source # 
NFData NodeSnapshot Source # 

Methods

rnf :: NodeSnapshot -> () #

FromXML NodeSnapshot Source # 
type Rep NodeSnapshot Source # 
type Rep NodeSnapshot = D1 (MetaData "NodeSnapshot" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "NodeSnapshot'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_nsNodeGroupConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NodeGroupConfiguration))) ((:*:) (S1 (MetaSel (Just Symbol "_nsCacheNodeCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))) (S1 (MetaSel (Just Symbol "_nsCacheClusterId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_nsCacheNodeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_nsNodeGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_nsSnapshotCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))) (S1 (MetaSel (Just Symbol "_nsCacheSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

nodeSnapshot :: NodeSnapshot Source #

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

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

nsNodeGroupConfiguration :: Lens' NodeSnapshot (Maybe NodeGroupConfiguration) Source #

The configuration for the source node group (shard).

nsCacheNodeCreateTime :: Lens' NodeSnapshot (Maybe UTCTime) Source #

The date and time when the cache node was created in the source cluster.

nsCacheClusterId :: Lens' NodeSnapshot (Maybe Text) Source #

A unique identifier for the source cluster.

nsCacheNodeId :: Lens' NodeSnapshot (Maybe Text) Source #

The cache node identifier for the node in the source cluster.

nsNodeGroupId :: Lens' NodeSnapshot (Maybe Text) Source #

A unique identifier for the source node group (shard).

nsSnapshotCreateTime :: Lens' NodeSnapshot (Maybe UTCTime) Source #

The date and time when the source node's metadata and cache data set was obtained for the snapshot.

nsCacheSize :: Lens' NodeSnapshot (Maybe Text) Source #

The size of the cache on the source cache node.

NotificationConfiguration

data NotificationConfiguration Source #

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

See: notificationConfiguration smart constructor.

Instances

Eq NotificationConfiguration Source # 
Data NotificationConfiguration Source # 

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 # 
Show NotificationConfiguration Source # 
Generic NotificationConfiguration Source # 
Hashable NotificationConfiguration Source # 
NFData NotificationConfiguration Source # 
FromXML NotificationConfiguration Source # 
type Rep NotificationConfiguration Source # 
type Rep NotificationConfiguration = D1 (MetaData "NotificationConfiguration" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "NotificationConfiguration'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ncTopicStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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 ElastiCache behavior.

See: parameter smart constructor.

Instances

Eq Parameter Source # 
Data Parameter Source # 

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 # 
Show Parameter Source # 
Generic Parameter Source # 

Associated Types

type Rep Parameter :: * -> * #

Hashable Parameter Source # 
NFData Parameter Source # 

Methods

rnf :: Parameter -> () #

FromXML Parameter Source # 
type Rep Parameter Source # 

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 of the parameter.
  • pMinimumEngineVersion - The earliest cache engine version to which the parameter can apply.
  • pSource - The source of the parameter.
  • pIsModifiable - Indicates whether (true ) or not (false ) the parameter can be modified. Some parameters have security or operational implications that prevent them from being changed.
  • pDataType - The valid data type for the parameter.
  • pAllowedValues - The valid range of values for the parameter.
  • pParameterName - The name of the parameter.
  • pDescription - A description of the parameter.
  • pChangeType - Indicates whether a change to the parameter is applied immediately or requires a reboot for the change to be applied. You can force a reboot or wait until the next maintenance window's reboot. For more information, see Rebooting a Cluster .

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

The value of the parameter.

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

The earliest cache engine version to which the parameter can apply.

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

The source of the parameter.

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

Indicates whether (true ) or not (false ) the parameter can be modified. Some parameters have security or operational implications that prevent them from being changed.

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

The valid data type for the parameter.

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

The valid range of values for the parameter.

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 #

Indicates whether a change to the parameter is applied immediately or requires a reboot for the change to be applied. You can force a reboot or wait until the next maintenance window's reboot. For more information, see Rebooting a Cluster .

ParameterNameValue

data ParameterNameValue Source #

Describes a name-value pair that is used to update the value of a parameter.

See: parameterNameValue smart constructor.

Instances

Eq ParameterNameValue Source # 
Data ParameterNameValue Source # 

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 # 
Show ParameterNameValue Source # 
Generic ParameterNameValue Source # 
Hashable ParameterNameValue Source # 
NFData ParameterNameValue Source # 

Methods

rnf :: ParameterNameValue -> () #

ToQuery ParameterNameValue Source # 
type Rep ParameterNameValue Source # 
type Rep ParameterNameValue = D1 (MetaData "ParameterNameValue" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "ParameterNameValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pnvParameterValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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.

PendingModifiedValues

data PendingModifiedValues Source #

A group of settings that are applied to the cluster in the future, or that are currently being applied.

See: pendingModifiedValues smart constructor.

Instances

Eq PendingModifiedValues Source # 
Data PendingModifiedValues Source # 

Methods

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

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

toConstr :: PendingModifiedValues -> Constr #

dataTypeOf :: PendingModifiedValues -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PendingModifiedValues Source # 
Show PendingModifiedValues Source # 
Generic PendingModifiedValues Source # 
Hashable PendingModifiedValues Source # 
NFData PendingModifiedValues Source # 

Methods

rnf :: PendingModifiedValues -> () #

FromXML PendingModifiedValues Source # 
type Rep PendingModifiedValues Source # 
type Rep PendingModifiedValues = D1 (MetaData "PendingModifiedValues" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "PendingModifiedValues'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pmvEngineVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pmvCacheNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_pmvCacheNodeIdsToRemove") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_pmvNumCacheNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))

pendingModifiedValues :: PendingModifiedValues Source #

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

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

  • pmvEngineVersion - The new cache engine version that the cluster runs.
  • pmvCacheNodeType - The cache node type that this cluster or replication group is scaled to.
  • pmvCacheNodeIdsToRemove - A list of cache node IDs that are being removed (or will be removed) from the cluster. A node ID is a numeric identifier (0001, 0002, etc.).
  • pmvNumCacheNodes - The new number of cache nodes for the cluster. For clusters running Redis, this value must be 1. For clusters running Memcached, this value must be between 1 and 20.

pmvEngineVersion :: Lens' PendingModifiedValues (Maybe Text) Source #

The new cache engine version that the cluster runs.

pmvCacheNodeType :: Lens' PendingModifiedValues (Maybe Text) Source #

The cache node type that this cluster or replication group is scaled to.

pmvCacheNodeIdsToRemove :: Lens' PendingModifiedValues [Text] Source #

A list of cache node IDs that are being removed (or will be removed) from the cluster. A node ID is a numeric identifier (0001, 0002, etc.).

pmvNumCacheNodes :: Lens' PendingModifiedValues (Maybe Int) Source #

The new number of cache nodes for the cluster. For clusters running Redis, this value must be 1. For clusters running Memcached, this value must be between 1 and 20.

RecurringCharge

data RecurringCharge Source #

Contains the specific price and frequency of a recurring charges for a reserved cache node, or for a reserved cache node offering.

See: recurringCharge smart constructor.

Instances

Eq RecurringCharge Source # 
Data RecurringCharge Source # 

Methods

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

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

toConstr :: RecurringCharge -> Constr #

dataTypeOf :: RecurringCharge -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RecurringCharge Source # 
Show RecurringCharge Source # 
Generic RecurringCharge Source # 
Hashable RecurringCharge Source # 
NFData RecurringCharge Source # 

Methods

rnf :: RecurringCharge -> () #

FromXML RecurringCharge Source # 
type Rep RecurringCharge Source # 
type Rep RecurringCharge = D1 (MetaData "RecurringCharge" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "RecurringCharge'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rcRecurringChargeFrequency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcRecurringChargeAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)))))

recurringCharge :: RecurringCharge Source #

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

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

rcRecurringChargeFrequency :: Lens' RecurringCharge (Maybe Text) Source #

The frequency of the recurring charge.

rcRecurringChargeAmount :: Lens' RecurringCharge (Maybe Double) Source #

The monetary amount of the recurring charge.

ReplicationGroup

data ReplicationGroup Source #

Contains all of the attributes of a specific Redis replication group.

See: replicationGroup smart constructor.

Instances

Eq ReplicationGroup Source # 
Data ReplicationGroup Source # 

Methods

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

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

toConstr :: ReplicationGroup -> Constr #

dataTypeOf :: ReplicationGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReplicationGroup Source # 
Show ReplicationGroup Source # 
Generic ReplicationGroup Source # 
Hashable ReplicationGroup Source # 
NFData ReplicationGroup Source # 

Methods

rnf :: ReplicationGroup -> () #

FromXML ReplicationGroup Source # 
type Rep ReplicationGroup Source # 
type Rep ReplicationGroup = D1 (MetaData "ReplicationGroup" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "ReplicationGroup'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rgStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rgCacheNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rgNodeGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [NodeGroup]))) (S1 (MetaSel (Just Symbol "_rgSnapshottingClusterId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rgClusterEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rgAtRestEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_rgTransitEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rgSnapshotWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rgConfigurationEndpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Endpoint))) (S1 (MetaSel (Just Symbol "_rgAuthTokenEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_rgMemberClusters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_rgSnapshotRetentionLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rgDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rgReplicationGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rgPendingModifiedValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReplicationGroupPendingModifiedValues))) (S1 (MetaSel (Just Symbol "_rgAutomaticFailover") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AutomaticFailoverStatus))))))))

replicationGroup :: ReplicationGroup Source #

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

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

  • rgStatus - The current state of this replication group - creating , available , modifying , deleting , create-failed , snapshotting .
  • rgCacheNodeType - The name of the compute and memory capacity node type for each node in the replication group.
  • rgNodeGroups - A list of node groups in this replication group. For Redis (cluster mode disabled) replication groups, this is a single-element list. For Redis (cluster mode enabled) replication groups, the list contains an entry for each node group (shard).
  • rgSnapshottingClusterId - The cluster ID that is used as the daily snapshot source for the replication group.
  • rgClusterEnabled - A flag indicating whether or not this replication group is cluster enabled; i.e., whether its data can be partitioned across multiple shards (API/CLI: node groups). Valid values: true | false
  • rgAtRestEncryptionEnabled - A flag that enables encryption at-rest when set to true . You cannot modify the value of AtRestEncryptionEnabled after the cluster is created. To enable encryption at-rest on a cluster you must set AtRestEncryptionEnabled to true when you create a cluster. Default: false
  • rgTransitEncryptionEnabled - A flag that enables in-transit encryption when set to true . You cannot modify the value of TransitEncryptionEnabled after the cluster is created. To enable in-transit encryption on a cluster you must set TransitEncryptionEnabled to true when you create a cluster. Default: false
  • rgSnapshotWindow - The daily time range (in UTC) during which ElastiCache begins taking a daily snapshot of your node group (shard). Example: 05:00-09:00 If you do not specify this parameter, ElastiCache automatically chooses an appropriate time range.
  • rgConfigurationEndpoint - The configuration endpoint for this replication group. Use the configuration endpoint to connect to this replication group.
  • rgAuthTokenEnabled - A flag that enables using an AuthToken (password) when issuing Redis commands. Default: false
  • rgMemberClusters - The identifiers of all the nodes that are part of this replication group.
  • rgSnapshotRetentionLimit - The number of days for which ElastiCache retains automatic cluster snapshots before deleting them. For example, if you set SnapshotRetentionLimit to 5, a snapshot that was taken today is retained for 5 days before being deleted. Important: If the value of SnapshotRetentionLimit is set to zero (0), backups are turned off.
  • rgDescription - The user supplied description of the replication group.
  • rgReplicationGroupId - The identifier for the replication group.
  • rgPendingModifiedValues - A group of settings to be applied to the replication group, either immediately or during the next maintenance window.
  • rgAutomaticFailover - Indicates the status of Multi-AZ with automatic failover for this Redis replication group. Amazon ElastiCache for Redis does not support Multi-AZ with automatic failover on: * Redis versions earlier than 2.8.6. * Redis (cluster mode disabled): T1 and T2 cache node types. * Redis (cluster mode enabled): T1 node types.

rgStatus :: Lens' ReplicationGroup (Maybe Text) Source #

The current state of this replication group - creating , available , modifying , deleting , create-failed , snapshotting .

rgCacheNodeType :: Lens' ReplicationGroup (Maybe Text) Source #

The name of the compute and memory capacity node type for each node in the replication group.

rgNodeGroups :: Lens' ReplicationGroup [NodeGroup] Source #

A list of node groups in this replication group. For Redis (cluster mode disabled) replication groups, this is a single-element list. For Redis (cluster mode enabled) replication groups, the list contains an entry for each node group (shard).

rgSnapshottingClusterId :: Lens' ReplicationGroup (Maybe Text) Source #

The cluster ID that is used as the daily snapshot source for the replication group.

rgClusterEnabled :: Lens' ReplicationGroup (Maybe Bool) Source #

A flag indicating whether or not this replication group is cluster enabled; i.e., whether its data can be partitioned across multiple shards (API/CLI: node groups). Valid values: true | false

rgAtRestEncryptionEnabled :: Lens' ReplicationGroup (Maybe Bool) Source #

A flag that enables encryption at-rest when set to true . You cannot modify the value of AtRestEncryptionEnabled after the cluster is created. To enable encryption at-rest on a cluster you must set AtRestEncryptionEnabled to true when you create a cluster. Default: false

rgTransitEncryptionEnabled :: Lens' ReplicationGroup (Maybe Bool) Source #

A flag that enables in-transit encryption when set to true . You cannot modify the value of TransitEncryptionEnabled after the cluster is created. To enable in-transit encryption on a cluster you must set TransitEncryptionEnabled to true when you create a cluster. Default: false

rgSnapshotWindow :: Lens' ReplicationGroup (Maybe Text) Source #

The daily time range (in UTC) during which ElastiCache begins taking a daily snapshot of your node group (shard). Example: 05:00-09:00 If you do not specify this parameter, ElastiCache automatically chooses an appropriate time range.

rgConfigurationEndpoint :: Lens' ReplicationGroup (Maybe Endpoint) Source #

The configuration endpoint for this replication group. Use the configuration endpoint to connect to this replication group.

rgAuthTokenEnabled :: Lens' ReplicationGroup (Maybe Bool) Source #

A flag that enables using an AuthToken (password) when issuing Redis commands. Default: false

rgMemberClusters :: Lens' ReplicationGroup [Text] Source #

The identifiers of all the nodes that are part of this replication group.

rgSnapshotRetentionLimit :: Lens' ReplicationGroup (Maybe Int) Source #

The number of days for which ElastiCache retains automatic cluster snapshots before deleting them. For example, if you set SnapshotRetentionLimit to 5, a snapshot that was taken today is retained for 5 days before being deleted. Important: If the value of SnapshotRetentionLimit is set to zero (0), backups are turned off.

rgDescription :: Lens' ReplicationGroup (Maybe Text) Source #

The user supplied description of the replication group.

rgReplicationGroupId :: Lens' ReplicationGroup (Maybe Text) Source #

The identifier for the replication group.

rgPendingModifiedValues :: Lens' ReplicationGroup (Maybe ReplicationGroupPendingModifiedValues) Source #

A group of settings to be applied to the replication group, either immediately or during the next maintenance window.

rgAutomaticFailover :: Lens' ReplicationGroup (Maybe AutomaticFailoverStatus) Source #

Indicates the status of Multi-AZ with automatic failover for this Redis replication group. Amazon ElastiCache for Redis does not support Multi-AZ with automatic failover on: * Redis versions earlier than 2.8.6. * Redis (cluster mode disabled): T1 and T2 cache node types. * Redis (cluster mode enabled): T1 node types.

ReplicationGroupPendingModifiedValues

data ReplicationGroupPendingModifiedValues Source #

The settings to be applied to the Redis replication group, either immediately or during the next maintenance window.

See: replicationGroupPendingModifiedValues smart constructor.

Instances

Eq ReplicationGroupPendingModifiedValues Source # 
Data ReplicationGroupPendingModifiedValues Source # 

Methods

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

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

toConstr :: ReplicationGroupPendingModifiedValues -> Constr #

dataTypeOf :: ReplicationGroupPendingModifiedValues -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReplicationGroupPendingModifiedValues Source # 
Show ReplicationGroupPendingModifiedValues Source # 
Generic ReplicationGroupPendingModifiedValues Source # 
Hashable ReplicationGroupPendingModifiedValues Source # 
NFData ReplicationGroupPendingModifiedValues Source # 
FromXML ReplicationGroupPendingModifiedValues Source # 
type Rep ReplicationGroupPendingModifiedValues Source # 
type Rep ReplicationGroupPendingModifiedValues = D1 (MetaData "ReplicationGroupPendingModifiedValues" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "ReplicationGroupPendingModifiedValues'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rgpmvResharding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReshardingStatus))) ((:*:) (S1 (MetaSel (Just Symbol "_rgpmvPrimaryClusterId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rgpmvAutomaticFailoverStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PendingAutomaticFailoverStatus))))))

replicationGroupPendingModifiedValues :: ReplicationGroupPendingModifiedValues Source #

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

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

  • rgpmvResharding - The status of an online resharding operation.
  • rgpmvPrimaryClusterId - The primary cluster ID that is applied immediately (if --apply-immediately was specified), or during the next maintenance window.
  • rgpmvAutomaticFailoverStatus - Indicates the status of Multi-AZ with automatic failover for this Redis replication group. Amazon ElastiCache for Redis does not support Multi-AZ with automatic failover on: * Redis versions earlier than 2.8.6. * Redis (cluster mode disabled): T1 and T2 cache node types. * Redis (cluster mode enabled): T1 node types.

rgpmvPrimaryClusterId :: Lens' ReplicationGroupPendingModifiedValues (Maybe Text) Source #

The primary cluster ID that is applied immediately (if --apply-immediately was specified), or during the next maintenance window.

rgpmvAutomaticFailoverStatus :: Lens' ReplicationGroupPendingModifiedValues (Maybe PendingAutomaticFailoverStatus) Source #

Indicates the status of Multi-AZ with automatic failover for this Redis replication group. Amazon ElastiCache for Redis does not support Multi-AZ with automatic failover on: * Redis versions earlier than 2.8.6. * Redis (cluster mode disabled): T1 and T2 cache node types. * Redis (cluster mode enabled): T1 node types.

ReservedCacheNode

data ReservedCacheNode Source #

Represents the output of a PurchaseReservedCacheNodesOffering operation.

See: reservedCacheNode smart constructor.

Instances

Eq ReservedCacheNode Source # 
Data ReservedCacheNode Source # 

Methods

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

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

toConstr :: ReservedCacheNode -> Constr #

dataTypeOf :: ReservedCacheNode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReservedCacheNode Source # 
Show ReservedCacheNode Source # 
Generic ReservedCacheNode Source # 
Hashable ReservedCacheNode Source # 
NFData ReservedCacheNode Source # 

Methods

rnf :: ReservedCacheNode -> () #

FromXML ReservedCacheNode Source # 
type Rep ReservedCacheNode Source # 
type Rep ReservedCacheNode = D1 (MetaData "ReservedCacheNode" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "ReservedCacheNode'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcnCacheNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcnStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnProductDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnCacheNodeCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_rcnReservedCacheNodeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcnRecurringCharges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RecurringCharge]))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnOfferingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcnUsagePrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnFixedPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_rcnReservedCacheNodesOfferingId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

reservedCacheNode :: ReservedCacheNode Source #

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

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

  • rcnCacheNodeType - The cache node type for the reserved cache nodes. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .
  • rcnState - The state of the reserved cache node.
  • rcnStartTime - The time the reservation started.
  • rcnProductDescription - The description of the reserved cache node.
  • rcnCacheNodeCount - The number of cache nodes that have been reserved.
  • rcnReservedCacheNodeId - The unique identifier for the reservation.
  • rcnRecurringCharges - The recurring price charged to run this reserved cache node.
  • rcnOfferingType - The offering type of this reserved cache node.
  • rcnUsagePrice - The hourly price charged for this reserved cache node.
  • rcnFixedPrice - The fixed price charged for this reserved cache node.
  • rcnDuration - The duration of the reservation in seconds.
  • rcnReservedCacheNodesOfferingId - The offering identifier.

rcnCacheNodeType :: Lens' ReservedCacheNode (Maybe Text) Source #

The cache node type for the reserved cache nodes. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .

rcnState :: Lens' ReservedCacheNode (Maybe Text) Source #

The state of the reserved cache node.

rcnStartTime :: Lens' ReservedCacheNode (Maybe UTCTime) Source #

The time the reservation started.

rcnProductDescription :: Lens' ReservedCacheNode (Maybe Text) Source #

The description of the reserved cache node.

rcnCacheNodeCount :: Lens' ReservedCacheNode (Maybe Int) Source #

The number of cache nodes that have been reserved.

rcnReservedCacheNodeId :: Lens' ReservedCacheNode (Maybe Text) Source #

The unique identifier for the reservation.

rcnRecurringCharges :: Lens' ReservedCacheNode [RecurringCharge] Source #

The recurring price charged to run this reserved cache node.

rcnOfferingType :: Lens' ReservedCacheNode (Maybe Text) Source #

The offering type of this reserved cache node.

rcnUsagePrice :: Lens' ReservedCacheNode (Maybe Double) Source #

The hourly price charged for this reserved cache node.

rcnFixedPrice :: Lens' ReservedCacheNode (Maybe Double) Source #

The fixed price charged for this reserved cache node.

rcnDuration :: Lens' ReservedCacheNode (Maybe Int) Source #

The duration of the reservation in seconds.

ReservedCacheNodesOffering

data ReservedCacheNodesOffering Source #

Describes all of the attributes of a reserved cache node offering.

See: reservedCacheNodesOffering smart constructor.

Instances

Eq ReservedCacheNodesOffering Source # 
Data ReservedCacheNodesOffering Source # 

Methods

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

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

toConstr :: ReservedCacheNodesOffering -> Constr #

dataTypeOf :: ReservedCacheNodesOffering -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReservedCacheNodesOffering Source # 
Show ReservedCacheNodesOffering Source # 
Generic ReservedCacheNodesOffering Source # 
Hashable ReservedCacheNodesOffering Source # 
NFData ReservedCacheNodesOffering Source # 
FromXML ReservedCacheNodesOffering Source # 
type Rep ReservedCacheNodesOffering Source # 
type Rep ReservedCacheNodesOffering = D1 (MetaData "ReservedCacheNodesOffering" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "ReservedCacheNodesOffering'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcnoCacheNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcnoProductDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnoRecurringCharges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RecurringCharge]))) (S1 (MetaSel (Just Symbol "_rcnoOfferingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcnoUsagePrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))) (S1 (MetaSel (Just Symbol "_rcnoFixedPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)))) ((:*:) (S1 (MetaSel (Just Symbol "_rcnoDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_rcnoReservedCacheNodesOfferingId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

reservedCacheNodesOffering :: ReservedCacheNodesOffering Source #

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

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

  • rcnoCacheNodeType - The cache node type for the reserved cache node. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .
  • rcnoProductDescription - The cache engine used by the offering.
  • rcnoRecurringCharges - The recurring price charged to run this reserved cache node.
  • rcnoOfferingType - The offering type.
  • rcnoUsagePrice - The hourly price charged for this offering.
  • rcnoFixedPrice - The fixed price charged for this offering.
  • rcnoDuration - The duration of the offering. in seconds.
  • rcnoReservedCacheNodesOfferingId - A unique identifier for the reserved cache node offering.

rcnoCacheNodeType :: Lens' ReservedCacheNodesOffering (Maybe Text) Source #

The cache node type for the reserved cache node. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .

rcnoProductDescription :: Lens' ReservedCacheNodesOffering (Maybe Text) Source #

The cache engine used by the offering.

rcnoRecurringCharges :: Lens' ReservedCacheNodesOffering [RecurringCharge] Source #

The recurring price charged to run this reserved cache node.

rcnoUsagePrice :: Lens' ReservedCacheNodesOffering (Maybe Double) Source #

The hourly price charged for this offering.

rcnoFixedPrice :: Lens' ReservedCacheNodesOffering (Maybe Double) Source #

The fixed price charged for this offering.

rcnoDuration :: Lens' ReservedCacheNodesOffering (Maybe Int) Source #

The duration of the offering. in seconds.

rcnoReservedCacheNodesOfferingId :: Lens' ReservedCacheNodesOffering (Maybe Text) Source #

A unique identifier for the reserved cache node offering.

ReshardingConfiguration

data ReshardingConfiguration Source #

A list of PreferredAvailabilityZones objects that specifies the configuration of a node group in the resharded cluster.

See: reshardingConfiguration smart constructor.

Instances

Eq ReshardingConfiguration Source # 
Data ReshardingConfiguration Source # 

Methods

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

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

toConstr :: ReshardingConfiguration -> Constr #

dataTypeOf :: ReshardingConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReshardingConfiguration Source # 
Show ReshardingConfiguration Source # 
Generic ReshardingConfiguration Source # 
Hashable ReshardingConfiguration Source # 
NFData ReshardingConfiguration Source # 

Methods

rnf :: ReshardingConfiguration -> () #

ToQuery ReshardingConfiguration Source # 
type Rep ReshardingConfiguration Source # 
type Rep ReshardingConfiguration = D1 (MetaData "ReshardingConfiguration" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" True) (C1 (MetaCons "ReshardingConfiguration'" PrefixI True) (S1 (MetaSel (Just Symbol "_rcPreferredAvailabilityZones") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

reshardingConfiguration :: ReshardingConfiguration Source #

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

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

rcPreferredAvailabilityZones :: Lens' ReshardingConfiguration [Text] Source #

A list of preferred availability zones for the nodes in this cluster.

ReshardingStatus

data ReshardingStatus Source #

The status of an online resharding operation.

See: reshardingStatus smart constructor.

Instances

Eq ReshardingStatus Source # 
Data ReshardingStatus Source # 

Methods

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

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

toConstr :: ReshardingStatus -> Constr #

dataTypeOf :: ReshardingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReshardingStatus Source # 
Show ReshardingStatus Source # 
Generic ReshardingStatus Source # 
Hashable ReshardingStatus Source # 
NFData ReshardingStatus Source # 

Methods

rnf :: ReshardingStatus -> () #

FromXML ReshardingStatus Source # 
type Rep ReshardingStatus Source # 
type Rep ReshardingStatus = D1 (MetaData "ReshardingStatus" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" True) (C1 (MetaCons "ReshardingStatus'" PrefixI True) (S1 (MetaSel (Just Symbol "_rsSlotMigration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SlotMigration))))

reshardingStatus :: ReshardingStatus Source #

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

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

  • rsSlotMigration - Represents the progress of an online resharding operation.

rsSlotMigration :: Lens' ReshardingStatus (Maybe SlotMigration) Source #

Represents the progress of an online resharding operation.

SecurityGroupMembership

data SecurityGroupMembership Source #

Represents a single cache security group and its status.

See: securityGroupMembership smart constructor.

Instances

Eq SecurityGroupMembership Source # 
Data SecurityGroupMembership Source # 

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 # 
Show SecurityGroupMembership Source # 
Generic SecurityGroupMembership Source # 
Hashable SecurityGroupMembership Source # 
NFData SecurityGroupMembership Source # 

Methods

rnf :: SecurityGroupMembership -> () #

FromXML SecurityGroupMembership Source # 
type Rep SecurityGroupMembership Source # 
type Rep SecurityGroupMembership = D1 (MetaData "SecurityGroupMembership" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "SecurityGroupMembership'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sgmStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sgmSecurityGroupId") 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 - The status of the cache security group membership. The status changes whenever a cache security group is modified, or when the cache security groups assigned to a cluster are modified.
  • sgmSecurityGroupId - The identifier of the cache security group.

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

The status of the cache security group membership. The status changes whenever a cache security group is modified, or when the cache security groups assigned to a cluster are modified.

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

The identifier of the cache security group.

SlotMigration

data SlotMigration Source #

Represents the progress of an online resharding operation.

See: slotMigration smart constructor.

Instances

Eq SlotMigration Source # 
Data SlotMigration Source # 

Methods

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

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

toConstr :: SlotMigration -> Constr #

dataTypeOf :: SlotMigration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SlotMigration Source # 
Show SlotMigration Source # 
Generic SlotMigration Source # 

Associated Types

type Rep SlotMigration :: * -> * #

Hashable SlotMigration Source # 
NFData SlotMigration Source # 

Methods

rnf :: SlotMigration -> () #

FromXML SlotMigration Source # 
type Rep SlotMigration Source # 
type Rep SlotMigration = D1 (MetaData "SlotMigration" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" True) (C1 (MetaCons "SlotMigration'" PrefixI True) (S1 (MetaSel (Just Symbol "_smProgressPercentage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Double))))

slotMigration :: SlotMigration Source #

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

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

smProgressPercentage :: Lens' SlotMigration (Maybe Double) Source #

The percentage of the slot migration that is complete.

Snapshot

data Snapshot Source #

Represents a copy of an entire Redis cluster as of the time when the snapshot was taken.

See: snapshot smart constructor.

Instances

Eq Snapshot Source # 
Data Snapshot Source # 

Methods

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

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

toConstr :: Snapshot -> Constr #

dataTypeOf :: Snapshot -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Snapshot Source # 
Show Snapshot Source # 
Generic Snapshot Source # 

Associated Types

type Rep Snapshot :: * -> * #

Methods

from :: Snapshot -> Rep Snapshot x #

to :: Rep Snapshot x -> Snapshot #

Hashable Snapshot Source # 

Methods

hashWithSalt :: Int -> Snapshot -> Int #

hash :: Snapshot -> Int #

NFData Snapshot Source # 

Methods

rnf :: Snapshot -> () #

FromXML Snapshot Source # 
type Rep Snapshot Source # 
type Rep Snapshot = D1 (MetaData "Snapshot" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "Snapshot'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sEngineVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sCacheNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sCacheClusterCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))))) ((:*:) (S1 (MetaSel (Just Symbol "_sAutoMinorVersionUpgrade") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_sCacheParameterGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sReplicationGroupDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sSnapshotStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sSnapshotWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_sCacheClusterId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sEngine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sPreferredMaintenanceWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sTopicARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sNodeSnapshots") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [NodeSnapshot]))) (S1 (MetaSel (Just Symbol "_sCacheSubnetGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_sPreferredAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sNumNodeGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_sSnapshotRetentionLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sSnapshotName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sReplicationGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sNumCacheNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))) ((:*:) (S1 (MetaSel (Just Symbol "_sPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "_sAutomaticFailover") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AutomaticFailoverStatus))) (S1 (MetaSel (Just Symbol "_sSnapshotSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

snapshot :: Snapshot Source #

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

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

  • sEngineVersion - The version of the cache engine version that is used by the source cluster.
  • sCacheNodeType - The name of the compute and memory capacity node type for the source cluster. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .
  • sCacheClusterCreateTime - The date and time when the source cluster was created.
  • sAutoMinorVersionUpgrade - This parameter is currently disabled.
  • sCacheParameterGroupName - The cache parameter group that is associated with the source cluster.
  • sReplicationGroupDescription - A description of the source replication group.
  • sVPCId - The Amazon Virtual Private Cloud identifier (VPC ID) of the cache subnet group for the source cluster.
  • sSnapshotStatus - The status of the snapshot. Valid values: creating | available | restoring | copying | deleting .
  • sSnapshotWindow - The daily time range during which ElastiCache takes daily snapshots of the source cluster.
  • sCacheClusterId - The user-supplied identifier of the source cluster.
  • sEngine - The name of the cache engine (memcached or redis ) used by the source cluster.
  • sPreferredMaintenanceWindow - Specifies the weekly time range during which maintenance on the cluster is performed. It is specified as a range in the format ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window is a 60 minute period. Valid values for ddd are: * sun * mon * tue * wed * thu * fri * sat Example: sun:23:00-mon:01:30
  • sTopicARN - The Amazon Resource Name (ARN) for the topic used by the source cluster for publishing notifications.
  • sNodeSnapshots - A list of the cache nodes in the source cluster.
  • sCacheSubnetGroupName - The name of the cache subnet group associated with the source cluster.
  • sPreferredAvailabilityZone - The name of the Availability Zone in which the source cluster is located.
  • sNumNodeGroups - The number of node groups (shards) in this snapshot. When restoring from a snapshot, the number of node groups (shards) in the snapshot and in the restored replication group must be the same.
  • sSnapshotRetentionLimit - For an automatic snapshot, the number of days for which ElastiCache retains the snapshot before deleting it. For manual snapshots, this field reflects the SnapshotRetentionLimit for the source cluster when the snapshot was created. This field is otherwise ignored: Manual snapshots do not expire, and can only be deleted using the DeleteSnapshot operation. Important If the value of SnapshotRetentionLimit is set to zero (0), backups are turned off.
  • sSnapshotName - The name of a snapshot. For an automatic snapshot, the name is system-generated. For a manual snapshot, this is the user-provided name.
  • sReplicationGroupId - The unique identifier of the source replication group.
  • sNumCacheNodes - The number of cache nodes in the source cluster. For clusters running Redis, this value must be 1. For clusters running Memcached, this value must be between 1 and 20.
  • sPort - The port number used by each cache nodes in the source cluster.
  • sAutomaticFailover - Indicates the status of Multi-AZ with automatic failover for the source Redis replication group. Amazon ElastiCache for Redis does not support Multi-AZ with automatic failover on: * Redis versions earlier than 2.8.6. * Redis (cluster mode disabled): T1 and T2 cache node types. * Redis (cluster mode enabled): T1 node types.
  • sSnapshotSource - Indicates whether the snapshot is from an automatic backup (automated ) or was created manually (manual ).

sEngineVersion :: Lens' Snapshot (Maybe Text) Source #

The version of the cache engine version that is used by the source cluster.

sCacheNodeType :: Lens' Snapshot (Maybe Text) Source #

The name of the compute and memory capacity node type for the source cluster. The following node types are supported by ElastiCache. Generally speaking, the current generation types provide more memory and computational power at lower cost when compared to their equivalent previous generation counterparts. * General purpose: * Current generation: T2 node types: cache.t2.micro , cache.t2.small , cache.t2.medium M3 node types: cache.m3.medium , cache.m3.large , cache.m3.xlarge , cache.m3.2xlarge M4 node types: cache.m4.large , cache.m4.xlarge , cache.m4.2xlarge , cache.m4.4xlarge , cache.m4.10xlarge * Previous generation: (not recommended) T1 node types: cache.t1.micro M1 node types: cache.m1.small , cache.m1.medium , cache.m1.large , cache.m1.xlarge * Compute optimized: * Previous generation: (not recommended) C1 node types: cache.c1.xlarge * Memory optimized: * Current generation: R3 node types: cache.r3.large , cache.r3.xlarge , cache.r3.2xlarge , cache.r3.4xlarge , cache.r3.8xlarge * Previous generation: (not recommended) M2 node types: cache.m2.xlarge , cache.m2.2xlarge , cache.m2.4xlarge Notes: * All T2 instances are created in an Amazon Virtual Private Cloud (Amazon VPC). * Redis (cluster mode disabled): Redis backuprestore is not supported on T1 and T2 instances. * Redis (cluster mode enabled): Backuprestore is not supported on T1 instances. * Redis Append-only files (AOF) functionality is not supported for T1 or T2 instances. For a complete listing of node types and specifications, see Amazon ElastiCache Product Features and Details and either Cache Node Type-Specific Parameters for Memcached or Cache Node Type-Specific Parameters for Redis .

sCacheClusterCreateTime :: Lens' Snapshot (Maybe UTCTime) Source #

The date and time when the source cluster was created.

sAutoMinorVersionUpgrade :: Lens' Snapshot (Maybe Bool) Source #

This parameter is currently disabled.

sCacheParameterGroupName :: Lens' Snapshot (Maybe Text) Source #

The cache parameter group that is associated with the source cluster.

sReplicationGroupDescription :: Lens' Snapshot (Maybe Text) Source #

A description of the source replication group.

sVPCId :: Lens' Snapshot (Maybe Text) Source #

The Amazon Virtual Private Cloud identifier (VPC ID) of the cache subnet group for the source cluster.

sSnapshotStatus :: Lens' Snapshot (Maybe Text) Source #

The status of the snapshot. Valid values: creating | available | restoring | copying | deleting .

sSnapshotWindow :: Lens' Snapshot (Maybe Text) Source #

The daily time range during which ElastiCache takes daily snapshots of the source cluster.

sCacheClusterId :: Lens' Snapshot (Maybe Text) Source #

The user-supplied identifier of the source cluster.

sEngine :: Lens' Snapshot (Maybe Text) Source #

The name of the cache engine (memcached or redis ) used by the source cluster.

sPreferredMaintenanceWindow :: Lens' Snapshot (Maybe Text) Source #

Specifies the weekly time range during which maintenance on the cluster is performed. It is specified as a range in the format ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window is a 60 minute period. Valid values for ddd are: * sun * mon * tue * wed * thu * fri * sat Example: sun:23:00-mon:01:30

sTopicARN :: Lens' Snapshot (Maybe Text) Source #

The Amazon Resource Name (ARN) for the topic used by the source cluster for publishing notifications.

sNodeSnapshots :: Lens' Snapshot [NodeSnapshot] Source #

A list of the cache nodes in the source cluster.

sCacheSubnetGroupName :: Lens' Snapshot (Maybe Text) Source #

The name of the cache subnet group associated with the source cluster.

sPreferredAvailabilityZone :: Lens' Snapshot (Maybe Text) Source #

The name of the Availability Zone in which the source cluster is located.

sNumNodeGroups :: Lens' Snapshot (Maybe Int) Source #

The number of node groups (shards) in this snapshot. When restoring from a snapshot, the number of node groups (shards) in the snapshot and in the restored replication group must be the same.

sSnapshotRetentionLimit :: Lens' Snapshot (Maybe Int) Source #

For an automatic snapshot, the number of days for which ElastiCache retains the snapshot before deleting it. For manual snapshots, this field reflects the SnapshotRetentionLimit for the source cluster when the snapshot was created. This field is otherwise ignored: Manual snapshots do not expire, and can only be deleted using the DeleteSnapshot operation. Important If the value of SnapshotRetentionLimit is set to zero (0), backups are turned off.

sSnapshotName :: Lens' Snapshot (Maybe Text) Source #

The name of a snapshot. For an automatic snapshot, the name is system-generated. For a manual snapshot, this is the user-provided name.

sReplicationGroupId :: Lens' Snapshot (Maybe Text) Source #

The unique identifier of the source replication group.

sNumCacheNodes :: Lens' Snapshot (Maybe Int) Source #

The number of cache nodes in the source cluster. For clusters running Redis, this value must be 1. For clusters running Memcached, this value must be between 1 and 20.

sPort :: Lens' Snapshot (Maybe Int) Source #

The port number used by each cache nodes in the source cluster.

sAutomaticFailover :: Lens' Snapshot (Maybe AutomaticFailoverStatus) Source #

Indicates the status of Multi-AZ with automatic failover for the source Redis replication group. Amazon ElastiCache for Redis does not support Multi-AZ with automatic failover on: * Redis versions earlier than 2.8.6. * Redis (cluster mode disabled): T1 and T2 cache node types. * Redis (cluster mode enabled): T1 node types.

sSnapshotSource :: Lens' Snapshot (Maybe Text) Source #

Indicates whether the snapshot is from an automatic backup (automated ) or was created manually (manual ).

Subnet

data Subnet Source #

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

See: subnet smart constructor.

Instances

Eq Subnet Source # 

Methods

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

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

Data Subnet Source # 

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 # 
Show Subnet Source # 
Generic Subnet Source # 

Associated Types

type Rep Subnet :: * -> * #

Methods

from :: Subnet -> Rep Subnet x #

to :: Rep Subnet x -> Subnet #

Hashable Subnet Source # 

Methods

hashWithSalt :: Int -> Subnet -> Int #

hash :: Subnet -> Int #

NFData Subnet Source # 

Methods

rnf :: Subnet -> () #

FromXML Subnet Source # 
type Rep Subnet Source # 
type Rep Subnet = D1 (MetaData "Subnet" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "Subnet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sSubnetIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sSubnetAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AvailabilityZone)))))

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 unique identifier for the subnet.

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

The Availability Zone associated with the subnet.

Tag

data Tag Source #

A cost allocation Tag that can be added to an ElastiCache cluster or replication group. Tags are composed of a Key/Value pair. A tag with a null Value is permitted.

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

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

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

Data Tag Source # 

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 # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

NFData Tag Source # 

Methods

rnf :: Tag -> () #

FromXML Tag Source # 

Methods

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

ToQuery Tag Source # 

Methods

toQuery :: Tag -> QueryString #

type Rep Tag Source # 
type Rep Tag = D1 (MetaData "Tag" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" False) (C1 (MetaCons "Tag'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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 tag's value. May be null.
  • tagKey - The key for the tag. May not be null.

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

The tag's value. May be null.

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

The key for the tag. May not be null.

TagListMessage

data TagListMessage Source #

Represents the output from the AddTagsToResource , ListTagsForResource , and RemoveTagsFromResource operations.

See: tagListMessage smart constructor.

Instances

Eq TagListMessage Source # 
Data TagListMessage Source # 

Methods

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

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

toConstr :: TagListMessage -> Constr #

dataTypeOf :: TagListMessage -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TagListMessage Source # 
Show TagListMessage Source # 
Generic TagListMessage Source # 

Associated Types

type Rep TagListMessage :: * -> * #

Hashable TagListMessage Source # 
NFData TagListMessage Source # 

Methods

rnf :: TagListMessage -> () #

FromXML TagListMessage Source # 
type Rep TagListMessage Source # 
type Rep TagListMessage = D1 (MetaData "TagListMessage" "Network.AWS.ElastiCache.Types.Product" "amazonka-elasticache-1.5.0-3KxmcjA9oxuJn4AiPGdjQZ" True) (C1 (MetaCons "TagListMessage'" PrefixI True) (S1 (MetaSel (Just Symbol "_tlmTagList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Tag]))))

tagListMessage :: TagListMessage Source #

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

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

  • tlmTagList - A list of cost allocation tags as key-value pairs.

tlmTagList :: Lens' TagListMessage [Tag] Source #

A list of cost allocation tags as key-value pairs.