amazonka-route53-autonaming-1.6.1: Amazon Route 53 Auto Naming SDK.

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

Network.AWS.Route53AutoNaming.Types

Contents

Description

 
Synopsis

Service Configuration

route53AutoNaming :: Service Source #

API version 2017-03-14 of the Amazon Route 53 Auto Naming SDK configuration.

Errors

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

The resource can't be created because you've reached the limit on the number of resources.

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

One or more specified values aren't valid. For example, when you're creating a namespace, the value of Name might not be a valid DNS name.

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

The namespace that you're trying to create already exists.

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

No namespace exists with the specified ID.

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

The service can't be created because a service with the same name already exists.

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

The specified resource can't be deleted because it contains other resources. For example, you can't delete a service that contains any instances.

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

Prism for CustomHealthNotFound' errors.

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

No instance exists with the specified ID, or the instance was recently registered, and information about the instance hasn't propagated yet.

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

The operation is already in progress.

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

No service exists with the specified ID.

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

No operation exists with the specified ID.

CustomHealthStatus

data CustomHealthStatus Source #

Constructors

CHSHealthy 
CHSUnhealthy 
Instances
Bounded CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: CustomHealthStatus -> Constr #

dataTypeOf :: CustomHealthStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep CustomHealthStatus :: Type -> Type #

Hashable CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: CustomHealthStatus -> () #

type Rep CustomHealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep CustomHealthStatus = D1 (MetaData "CustomHealthStatus" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "CHSHealthy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CHSUnhealthy" PrefixI False) (U1 :: Type -> Type))

FilterCondition

data FilterCondition Source #

Constructors

Between 
EQ' 
IN 
Instances
Bounded FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: FilterCondition -> Constr #

dataTypeOf :: FilterCondition -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep FilterCondition :: Type -> Type #

Hashable FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: FilterCondition -> () #

type Rep FilterCondition Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep FilterCondition = D1 (MetaData "FilterCondition" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "Between" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EQ'" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IN" PrefixI False) (U1 :: Type -> Type)))

HealthCheckType

data HealthCheckType Source #

Constructors

HTTP 
HTTPS 
TCP 
Instances
Bounded HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: HealthCheckType -> Constr #

dataTypeOf :: HealthCheckType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep HealthCheckType :: Type -> Type #

Hashable HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: HealthCheckType -> () #

type Rep HealthCheckType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep HealthCheckType = D1 (MetaData "HealthCheckType" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "HTTP" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HTTPS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TCP" PrefixI False) (U1 :: Type -> Type)))

HealthStatus

data HealthStatus Source #

Constructors

Healthy 
Unhealthy 
Unknown 
Instances
Bounded HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: HealthStatus -> Constr #

dataTypeOf :: HealthStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep HealthStatus :: Type -> Type #

Hashable HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

toText :: HealthStatus -> Text #

NFData HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: HealthStatus -> () #

type Rep HealthStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep HealthStatus = D1 (MetaData "HealthStatus" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "Healthy" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Unhealthy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Unknown" PrefixI False) (U1 :: Type -> Type)))

NamespaceFilterName

data NamespaceFilterName Source #

Constructors

Type 
Instances
Bounded NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: NamespaceFilterName -> Constr #

dataTypeOf :: NamespaceFilterName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep NamespaceFilterName :: Type -> Type #

Hashable NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: NamespaceFilterName -> () #

type Rep NamespaceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep NamespaceFilterName = D1 (MetaData "NamespaceFilterName" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "Type" PrefixI False) (U1 :: Type -> Type))

NamespaceType

data NamespaceType Source #

Constructors

DNSPrivate 
DNSPublic 
Instances
Bounded NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: NamespaceType -> Constr #

dataTypeOf :: NamespaceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep NamespaceType :: Type -> Type #

Hashable NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

toText :: NamespaceType -> Text #

NFData NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: NamespaceType -> () #

type Rep NamespaceType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep NamespaceType = D1 (MetaData "NamespaceType" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "DNSPrivate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DNSPublic" PrefixI False) (U1 :: Type -> Type))

OperationFilterName

data OperationFilterName Source #

Instances
Bounded OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: OperationFilterName -> Constr #

dataTypeOf :: OperationFilterName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep OperationFilterName :: Type -> Type #

Hashable OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: OperationFilterName -> () #

type Rep OperationFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep OperationFilterName = D1 (MetaData "OperationFilterName" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) ((C1 (MetaCons "OFNNamespaceId" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OFNServiceId" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OFNStatus" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OFNType" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OFNUpdateDate" PrefixI False) (U1 :: Type -> Type))))

OperationStatus

data OperationStatus Source #

Constructors

Fail 
Pending 
Submitted 
Success 
Instances
Bounded OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: OperationStatus -> Constr #

dataTypeOf :: OperationStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep OperationStatus :: Type -> Type #

Hashable OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: OperationStatus -> () #

type Rep OperationStatus Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep OperationStatus = D1 (MetaData "OperationStatus" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) ((C1 (MetaCons "Fail" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Pending" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Submitted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Success" PrefixI False) (U1 :: Type -> Type)))

OperationTargetType

data OperationTargetType Source #

Instances
Bounded OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: OperationTargetType -> Constr #

dataTypeOf :: OperationTargetType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep OperationTargetType :: Type -> Type #

Hashable OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: OperationTargetType -> () #

type Rep OperationTargetType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep OperationTargetType = D1 (MetaData "OperationTargetType" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "OTTInstance" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OTTNamespace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OTTService" PrefixI False) (U1 :: Type -> Type)))

OperationType

data OperationType Source #

Instances
Bounded OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: OperationType -> Constr #

dataTypeOf :: OperationType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep OperationType :: Type -> Type #

Hashable OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

toText :: OperationType -> Text #

NFData OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: OperationType -> () #

type Rep OperationType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep OperationType = D1 (MetaData "OperationType" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) ((C1 (MetaCons "CreateNamespace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DeleteNamespace" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DeregisterInstance" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RegisterInstance" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UpdateService" PrefixI False) (U1 :: Type -> Type))))

RecordType

data RecordType Source #

Constructors

A 
Aaaa 
Cname 
Srv 
Instances
Bounded RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: RecordType -> Constr #

dataTypeOf :: RecordType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep RecordType :: Type -> Type #

Hashable RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

toText :: RecordType -> Text #

NFData RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: RecordType -> () #

type Rep RecordType Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep RecordType = D1 (MetaData "RecordType" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) ((C1 (MetaCons "A" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Aaaa" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Cname" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Srv" PrefixI False) (U1 :: Type -> Type)))

RoutingPolicy

data RoutingPolicy Source #

Constructors

Multivalue 
Weighted 
Instances
Bounded RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: RoutingPolicy -> Constr #

dataTypeOf :: RoutingPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep RoutingPolicy :: Type -> Type #

Hashable RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromJSON RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

toText :: RoutingPolicy -> Text #

NFData RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: RoutingPolicy -> () #

type Rep RoutingPolicy Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep RoutingPolicy = D1 (MetaData "RoutingPolicy" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "Multivalue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Weighted" PrefixI False) (U1 :: Type -> Type))

ServiceFilterName

data ServiceFilterName Source #

Constructors

NamespaceId 
Instances
Bounded ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Enum ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Eq ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Data ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

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

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

toConstr :: ServiceFilterName -> Constr #

dataTypeOf :: ServiceFilterName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Read ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Show ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Generic ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Associated Types

type Rep ServiceFilterName :: Type -> Type #

Hashable ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToJSON ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToHeader ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToQuery ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToByteString ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

FromText ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

ToText ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

NFData ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

Methods

rnf :: ServiceFilterName -> () #

type Rep ServiceFilterName Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Sum

type Rep ServiceFilterName = D1 (MetaData "ServiceFilterName" "Network.AWS.Route53AutoNaming.Types.Sum" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "NamespaceId" PrefixI False) (U1 :: Type -> Type))

DNSConfig

data DNSConfig Source #

A complex type that contains information about the records that you want Amazon Route 53 to create when you register an instance.

See: dnsConfig smart constructor.

Instances
Eq DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: DNSConfig -> Constr #

dataTypeOf :: DNSConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep DNSConfig :: Type -> Type #

Hashable DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: DNSConfig -> () #

type Rep DNSConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep DNSConfig = D1 (MetaData "DNSConfig" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "DNSConfig'" PrefixI True) (S1 (MetaSel (Just "_dcRoutingPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RoutingPolicy)) :*: (S1 (MetaSel (Just "_dcNamespaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_dcDNSRecords") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [DNSRecord]))))

dnsConfig Source #

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

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

  • dcRoutingPolicy - The routing policy that you want to apply to all records that Route 53 creates when you register an instance and specify this service. You can specify the following values: MULTIVALUE If you define a health check for the service and the health check is healthy, Route 53 returns the applicable value for up to eight instances. For example, suppose the service includes configurations for one A record and a health check, and you use the service to register 10 instances. Route 53 responds to DNS queries with IP addresses for up to eight healthy instances. If fewer than eight instances are healthy, Route 53 responds to every DNS query with the IP addresses for all of the healthy instances. If you don't define a health check for the service, Route 53 assumes that all instances are healthy and returns the values for up to eight instances. For more information about the multivalue routing policy, see Multivalue Answer Routing in the Route 53 Developer Guide . WEIGHTED Route 53 returns the applicable value from one randomly selected instance from among the instances that you registered using the same service. Currently, all records have the same weight, so you can't route more or less traffic to any instances. For example, suppose the service includes configurations for one A record and a health check, and you use the service to register 10 instances. Route 53 responds to DNS queries with the IP address for one randomly selected instance from among the healthy instances. If no instances are healthy, Route 53 responds to DNS queries as if all of the instances were healthy. If you don't define a health check for the service, Route 53 assumes that all instances are healthy and returns the applicable value for one randomly selected instance. For more information about the weighted routing policy, see Weighted Routing in the Route 53 Developer Guide .
  • dcNamespaceId - The ID of the namespace to use for DNS configuration.
  • dcDNSRecords - An array that contains one DnsRecord object for each record that you want Route 53 to create when you register an instance.

dcRoutingPolicy :: Lens' DNSConfig (Maybe RoutingPolicy) Source #

The routing policy that you want to apply to all records that Route 53 creates when you register an instance and specify this service. You can specify the following values: MULTIVALUE If you define a health check for the service and the health check is healthy, Route 53 returns the applicable value for up to eight instances. For example, suppose the service includes configurations for one A record and a health check, and you use the service to register 10 instances. Route 53 responds to DNS queries with IP addresses for up to eight healthy instances. If fewer than eight instances are healthy, Route 53 responds to every DNS query with the IP addresses for all of the healthy instances. If you don't define a health check for the service, Route 53 assumes that all instances are healthy and returns the values for up to eight instances. For more information about the multivalue routing policy, see Multivalue Answer Routing in the Route 53 Developer Guide . WEIGHTED Route 53 returns the applicable value from one randomly selected instance from among the instances that you registered using the same service. Currently, all records have the same weight, so you can't route more or less traffic to any instances. For example, suppose the service includes configurations for one A record and a health check, and you use the service to register 10 instances. Route 53 responds to DNS queries with the IP address for one randomly selected instance from among the healthy instances. If no instances are healthy, Route 53 responds to DNS queries as if all of the instances were healthy. If you don't define a health check for the service, Route 53 assumes that all instances are healthy and returns the applicable value for one randomly selected instance. For more information about the weighted routing policy, see Weighted Routing in the Route 53 Developer Guide .

dcNamespaceId :: Lens' DNSConfig Text Source #

The ID of the namespace to use for DNS configuration.

dcDNSRecords :: Lens' DNSConfig [DNSRecord] Source #

An array that contains one DnsRecord object for each record that you want Route 53 to create when you register an instance.

DNSConfigChange

data DNSConfigChange Source #

A complex type that contains information about changes to the records that Route 53 creates when you register an instance.

See: dnsConfigChange smart constructor.

Instances
Eq DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: DNSConfigChange -> Constr #

dataTypeOf :: DNSConfigChange -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep DNSConfigChange :: Type -> Type #

Hashable DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: DNSConfigChange -> () #

type Rep DNSConfigChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep DNSConfigChange = D1 (MetaData "DNSConfigChange" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" True) (C1 (MetaCons "DNSConfigChange'" PrefixI True) (S1 (MetaSel (Just "_dccDNSRecords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DNSRecord])))

dnsConfigChange :: DNSConfigChange Source #

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

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

  • dccDNSRecords - An array that contains one DnsRecord object for each record that you want Route 53 to create when you register an instance.

dccDNSRecords :: Lens' DNSConfigChange [DNSRecord] Source #

An array that contains one DnsRecord object for each record that you want Route 53 to create when you register an instance.

DNSProperties

data DNSProperties Source #

A complex type that contains the ID for the hosted zone that Route 53 creates when you create a namespace.

See: dnsProperties smart constructor.

Instances
Eq DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: DNSProperties -> Constr #

dataTypeOf :: DNSProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep DNSProperties :: Type -> Type #

Hashable DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: DNSProperties -> () #

type Rep DNSProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep DNSProperties = D1 (MetaData "DNSProperties" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" True) (C1 (MetaCons "DNSProperties'" PrefixI True) (S1 (MetaSel (Just "_dpHostedZoneId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

dnsProperties :: DNSProperties Source #

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

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

  • dpHostedZoneId - The ID for the hosted zone that Route 53 creates when you create a namespace.

dpHostedZoneId :: Lens' DNSProperties (Maybe Text) Source #

The ID for the hosted zone that Route 53 creates when you create a namespace.

DNSRecord

data DNSRecord Source #

A complex type that contains information about the records that you want Route 53 to create when you register an instance.

See: dnsRecord smart constructor.

Instances
Eq DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: DNSRecord -> Constr #

dataTypeOf :: DNSRecord -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep DNSRecord :: Type -> Type #

Hashable DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: DNSRecord -> () #

type Rep DNSRecord Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep DNSRecord = D1 (MetaData "DNSRecord" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "DNSRecord'" PrefixI True) (S1 (MetaSel (Just "_drType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RecordType) :*: S1 (MetaSel (Just "_drTTL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat)))

dnsRecord Source #

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

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

  • drType - The type of the resource, which indicates the type of value that Route 53 returns in response to DNS queries. Note the following: * A, AAAA, and SRV records: You can specify settings for a maximum of one A, one AAAA, and one SRV record. You can specify them in any combination. * CNAME records: If you specify CNAME for Type , you can't define any other records. This is a limitation of DNS—you can't create a CNAME record and any other type of record that has the same name as a CNAME record. * Alias records: If you want Route 53 to create an alias record when you register an instance, specify A or AAAA for Type . * All records: You specify settings other than TTL and Type when you register an instance. The following values are supported: A Route 53 returns the IP address of the resource in IPv4 format, such as 192.0.2.44. AAAA Route 53 returns the IP address of the resource in IPv6 format, such as 2001:0db8:85a3:0000:0000:abcd:0001:2345. CNAME Route 53 returns the domain name of the resource, such as www.example.com. Note the following: * You specify the domain name that you want to route traffic to when you register an instance. For more information, see 'RegisterInstanceRequest$Attributes' . * You must specify WEIGHTED for the value of RoutingPolicy . * You can't specify both CNAME for Type and settings for HealthCheckConfig . If you do, the request will fail with an InvalidInput error. SRV Route 53 returns the value for an SRV record. The value for an SRV record uses the following values: priority weight port service-hostname Note the following about the values: * The values of priority and weight are both set to 1 and can't be changed. * The value of port comes from the value that you specify for the AWS_INSTANCE_PORT attribute when you submit a RegisterInstance request. * The value of service-hostname is a concatenation of the following values: * The value that you specify for InstanceId when you register an instance. * The name of the service. * The name of the namespace. For example, if the value of InstanceId is test , the name of the service is backend , and the name of the namespace is example.com , the value of service-hostname is: test.backend.example.com If you specify settings for an SRV record and if you specify values for AWS_INSTANCE_IPV4 , AWS_INSTANCE_IPV6 , or both in the RegisterInstance request, Route 53 automatically creates A and/or AAAA records that have the same name as the value of service-hostname in the SRV record. You can ignore these records.
  • drTTL - The amount of time, in seconds, that you want DNS resolvers to cache the settings for this record.

drType :: Lens' DNSRecord RecordType Source #

The type of the resource, which indicates the type of value that Route 53 returns in response to DNS queries. Note the following: * A, AAAA, and SRV records: You can specify settings for a maximum of one A, one AAAA, and one SRV record. You can specify them in any combination. * CNAME records: If you specify CNAME for Type , you can't define any other records. This is a limitation of DNS—you can't create a CNAME record and any other type of record that has the same name as a CNAME record. * Alias records: If you want Route 53 to create an alias record when you register an instance, specify A or AAAA for Type . * All records: You specify settings other than TTL and Type when you register an instance. The following values are supported: A Route 53 returns the IP address of the resource in IPv4 format, such as 192.0.2.44. AAAA Route 53 returns the IP address of the resource in IPv6 format, such as 2001:0db8:85a3:0000:0000:abcd:0001:2345. CNAME Route 53 returns the domain name of the resource, such as www.example.com. Note the following: * You specify the domain name that you want to route traffic to when you register an instance. For more information, see 'RegisterInstanceRequest$Attributes' . * You must specify WEIGHTED for the value of RoutingPolicy . * You can't specify both CNAME for Type and settings for HealthCheckConfig . If you do, the request will fail with an InvalidInput error. SRV Route 53 returns the value for an SRV record. The value for an SRV record uses the following values: priority weight port service-hostname Note the following about the values: * The values of priority and weight are both set to 1 and can't be changed. * The value of port comes from the value that you specify for the AWS_INSTANCE_PORT attribute when you submit a RegisterInstance request. * The value of service-hostname is a concatenation of the following values: * The value that you specify for InstanceId when you register an instance. * The name of the service. * The name of the namespace. For example, if the value of InstanceId is test , the name of the service is backend , and the name of the namespace is example.com , the value of service-hostname is: test.backend.example.com If you specify settings for an SRV record and if you specify values for AWS_INSTANCE_IPV4 , AWS_INSTANCE_IPV6 , or both in the RegisterInstance request, Route 53 automatically creates A and/or AAAA records that have the same name as the value of service-hostname in the SRV record. You can ignore these records.

drTTL :: Lens' DNSRecord Natural Source #

The amount of time, in seconds, that you want DNS resolvers to cache the settings for this record.

HealthCheckConfig

data HealthCheckConfig Source #

Public DNS namespaces only. A complex type that contains settings for an optional health check. If you specify settings for a health check, Amazon Route 53 associates the health check with all the records that you specify in DnsConfig .

A and AAAA records

If DnsConfig includes configurations for both A and AAAA records, Route 53 creates a health check that uses the IPv4 address to check the health of the resource. If the endpoint that is specified by the IPv4 address is unhealthy, Route 53 considers both the A and AAAA records to be unhealthy.

CNAME records

You can't specify settings for HealthCheckConfig when the DNSConfig includes CNAME for the value of Type . If you do, the CreateService request will fail with an InvalidInput error.

Request interval

The health check uses 30 seconds as the request interval. This is the number of seconds between the time that each Route 53 health checker gets a response from your endpoint and the time that it sends the next health check request. A health checker in each data center around the world sends your endpoint a health check request every 30 seconds. On average, your endpoint receives a health check request about every two seconds. Health checkers in different data centers don't coordinate with one another, so you'll sometimes see several requests per second followed by a few seconds with no health checks at all.

Health checking regions

Health checkers perform checks from all Route 53 health-checking regions. For a list of the current regions, see Regions .

Alias records

When you register an instance, if you include the AWS_ALIAS_DNS_NAME attribute, Route 53 creates an alias record. Note the following:

  • Route 53 automatically sets EvaluateTargetHealth to true for alias records. When EvaluateTargetHealth is true, the alias record inherits the health of the referenced AWS resource. such as an ELB load balancer. For more information, see EvaluateTargetHealth .
  • If you include HealthCheckConfig and then use the service to register an instance that creates an alias record, Route 53 doesn't create the health check.

For information about the charges for health checks, see Route 53 Pricing .

See: healthCheckConfig smart constructor.

Instances
Eq HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: HealthCheckConfig -> Constr #

dataTypeOf :: HealthCheckConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep HealthCheckConfig :: Type -> Type #

Hashable HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: HealthCheckConfig -> () #

type Rep HealthCheckConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep HealthCheckConfig = D1 (MetaData "HealthCheckConfig" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "HealthCheckConfig'" PrefixI True) (S1 (MetaSel (Just "_hccFailureThreshold") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)) :*: (S1 (MetaSel (Just "_hccResourcePath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_hccType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HealthCheckType)))))

healthCheckConfig :: HealthCheckConfig Source #

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

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

  • hccFailureThreshold - The number of consecutive health checks that an endpoint must pass or fail for Route 53 to change the current status of the endpoint from unhealthy to healthy or vice versa. For more information, see How Route 53 Determines Whether an Endpoint Is Healthy in the Route 53 Developer Guide .
  • hccResourcePath - The path that you want Route 53 to request when performing health checks. The path can be any value for which your endpoint will return an HTTP status code of 2xx or 3xx when the endpoint is healthy, such as the file docsroute53-health-check.html . Route 53 automatically adds the DNS name for the service and a leading forward slash (/ ) character.
  • hccType - The type of health check that you want to create, which indicates how Route 53 determines whether an endpoint is healthy. Important: You can't change the value of Type after you create a health check. You can create the following types of health checks: * HTTP : Route 53 tries to establish a TCP connection. If successful, Route 53 submits an HTTP request and waits for an HTTP status code of 200 or greater and less than 400. * HTTPS : Route 53 tries to establish a TCP connection. If successful, Route 53 submits an HTTPS request and waits for an HTTP status code of 200 or greater and less than 400. Important: If you specify HTTPS for the value of Type , the endpoint must support TLS v1.0 or later. * TCP : Route 53 tries to establish a TCP connection. For more information, see How Route 53 Determines Whether an Endpoint Is Healthy in the Route 53 Developer Guide .

hccFailureThreshold :: Lens' HealthCheckConfig (Maybe Natural) Source #

The number of consecutive health checks that an endpoint must pass or fail for Route 53 to change the current status of the endpoint from unhealthy to healthy or vice versa. For more information, see How Route 53 Determines Whether an Endpoint Is Healthy in the Route 53 Developer Guide .

hccResourcePath :: Lens' HealthCheckConfig (Maybe Text) Source #

The path that you want Route 53 to request when performing health checks. The path can be any value for which your endpoint will return an HTTP status code of 2xx or 3xx when the endpoint is healthy, such as the file docsroute53-health-check.html . Route 53 automatically adds the DNS name for the service and a leading forward slash (/ ) character.

hccType :: Lens' HealthCheckConfig (Maybe HealthCheckType) Source #

The type of health check that you want to create, which indicates how Route 53 determines whether an endpoint is healthy. Important: You can't change the value of Type after you create a health check. You can create the following types of health checks: * HTTP : Route 53 tries to establish a TCP connection. If successful, Route 53 submits an HTTP request and waits for an HTTP status code of 200 or greater and less than 400. * HTTPS : Route 53 tries to establish a TCP connection. If successful, Route 53 submits an HTTPS request and waits for an HTTP status code of 200 or greater and less than 400. Important: If you specify HTTPS for the value of Type , the endpoint must support TLS v1.0 or later. * TCP : Route 53 tries to establish a TCP connection. For more information, see How Route 53 Determines Whether an Endpoint Is Healthy in the Route 53 Developer Guide .

HealthCheckCustomConfig

data HealthCheckCustomConfig Source #

See: healthCheckCustomConfig smart constructor.

Instances
Eq HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: HealthCheckCustomConfig -> Constr #

dataTypeOf :: HealthCheckCustomConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep HealthCheckCustomConfig :: Type -> Type #

Hashable HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: HealthCheckCustomConfig -> () #

type Rep HealthCheckCustomConfig Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep HealthCheckCustomConfig = D1 (MetaData "HealthCheckCustomConfig" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" True) (C1 (MetaCons "HealthCheckCustomConfig'" PrefixI True) (S1 (MetaSel (Just "_hcccFailureThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Nat))))

healthCheckCustomConfig :: HealthCheckCustomConfig Source #

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

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

Instance

data Instance Source #

A complex type that contains information about an instance that Amazon Route 53 creates when you submit a RegisterInstance request.

See: instance' smart constructor.

Instances
Eq Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: Instance -> Constr #

dataTypeOf :: Instance -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep Instance :: Type -> Type #

Methods

from :: Instance -> Rep Instance x #

to :: Rep Instance x -> Instance #

Hashable Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

hashWithSalt :: Int -> Instance -> Int #

hash :: Instance -> Int #

FromJSON Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: Instance -> () #

type Rep Instance Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep Instance = D1 (MetaData "Instance" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "Instance'" PrefixI True) (S1 (MetaSel (Just "_iCreatorRequestId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_iAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text))) :*: S1 (MetaSel (Just "_iId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

instance' Source #

Arguments

:: Text

iId

-> Instance 

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

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

  • iCreatorRequestId - A unique string that identifies the request and that allows failed RegisterInstance requests to be retried without the risk of executing the operation twice. You must use a unique CreatorRequestId string every time you submit a RegisterInstance request if you're registering additional instances for the same namespace and service. CreatorRequestId can be any unique string, for example, a date/time stamp.
  • iAttributes - A string map that contains the following information for the service that you specify in ServiceId : * The attributes that apply to the records that are defined in the service. * For each attribute, the applicable value. Supported attribute keys include the following: AWS_ALIAS_DNS_NAME __ If you want Route 53 to create an alias record that routes traffic to an Elastic Load Balancing load balancer, specify the DNS name that is associated with the load balancer. For information about how to get the DNS name, see DNSName in the topic AliasTarget . Note the following: * The configuration for the service that is specified by ServiceId must include settings for an A record, an AAAA record, or both. * In the service that is specified by ServiceId , the value of RoutingPolicy must be WEIGHTED . * If the service that is specified by ServiceId includes HealthCheckConfig settings, Route 53 will create the health check, but it won't associate the health check with the alias record. * Auto naming currently doesn't support creating alias records that route traffic to AWS resources other than ELB load balancers. * If you specify a value for AWS_ALIAS_DNS_NAME , don't specify values for any of the AWS_INSTANCE attributes. AWS_INSTANCE_CNAME If the service configuration includes a CNAME record, the domain name that you want Route 53 to return in response to DNS queries, for example, example.com . This value is required if the service specified by ServiceId includes settings for an CNAME record. AWS_INSTANCE_IPV4 If the service configuration includes an A record, the IPv4 address that you want Route 53 to return in response to DNS queries, for example, 192.0.2.44 . This value is required if the service specified by ServiceId includes settings for an A record. If the service includes settings for an SRV record, you must specify a value for AWS_INSTANCE_IPV4 , AWS_INSTANCE_IPV6 , or both. AWS_INSTANCE_IPV6 If the service configuration includes an AAAA record, the IPv6 address that you want Route 53 to return in response to DNS queries, for example, 2001:0db8:85a3:0000:0000:abcd:0001:2345 . This value is required if the service specified by ServiceId includes settings for an AAAA record. If the service includes settings for an SRV record, you must specify a value for AWS_INSTANCE_IPV4 , AWS_INSTANCE_IPV6 , or both. AWS_INSTANCE_PORT__ If the service includes an SRV record, the value that you want Route 53 to return for the port. If the service includes HealthCheckConfig , the port on the endpoint that you want Route 53 to send requests to. This value is required if you specified settings for an SRV record when you created the service.
  • iId - An identifier that you want to associate with the instance. Note the following: * If the service that is specified by ServiceId includes settings for an SRV record, the value of InstanceId is automatically included as part of the value for the SRV record. For more information, see 'DnsRecord$Type' . * You can use this value to update an existing instance. * To register a new instance, you must specify a value that is unique among instances that you register by using the same service. * If you specify an existing InstanceId and ServiceId , Route 53 updates the existing records. If there's also an existing health check, Route 53 deletes the old health check and creates a new one.

iCreatorRequestId :: Lens' Instance (Maybe Text) Source #

A unique string that identifies the request and that allows failed RegisterInstance requests to be retried without the risk of executing the operation twice. You must use a unique CreatorRequestId string every time you submit a RegisterInstance request if you're registering additional instances for the same namespace and service. CreatorRequestId can be any unique string, for example, a date/time stamp.

iAttributes :: Lens' Instance (HashMap Text Text) Source #

A string map that contains the following information for the service that you specify in ServiceId : * The attributes that apply to the records that are defined in the service. * For each attribute, the applicable value. Supported attribute keys include the following: AWS_ALIAS_DNS_NAME __ If you want Route 53 to create an alias record that routes traffic to an Elastic Load Balancing load balancer, specify the DNS name that is associated with the load balancer. For information about how to get the DNS name, see DNSName in the topic AliasTarget . Note the following: * The configuration for the service that is specified by ServiceId must include settings for an A record, an AAAA record, or both. * In the service that is specified by ServiceId , the value of RoutingPolicy must be WEIGHTED . * If the service that is specified by ServiceId includes HealthCheckConfig settings, Route 53 will create the health check, but it won't associate the health check with the alias record. * Auto naming currently doesn't support creating alias records that route traffic to AWS resources other than ELB load balancers. * If you specify a value for AWS_ALIAS_DNS_NAME , don't specify values for any of the AWS_INSTANCE attributes. AWS_INSTANCE_CNAME If the service configuration includes a CNAME record, the domain name that you want Route 53 to return in response to DNS queries, for example, example.com . This value is required if the service specified by ServiceId includes settings for an CNAME record. AWS_INSTANCE_IPV4 If the service configuration includes an A record, the IPv4 address that you want Route 53 to return in response to DNS queries, for example, 192.0.2.44 . This value is required if the service specified by ServiceId includes settings for an A record. If the service includes settings for an SRV record, you must specify a value for AWS_INSTANCE_IPV4 , AWS_INSTANCE_IPV6 , or both. AWS_INSTANCE_IPV6 If the service configuration includes an AAAA record, the IPv6 address that you want Route 53 to return in response to DNS queries, for example, 2001:0db8:85a3:0000:0000:abcd:0001:2345 . This value is required if the service specified by ServiceId includes settings for an AAAA record. If the service includes settings for an SRV record, you must specify a value for AWS_INSTANCE_IPV4 , AWS_INSTANCE_IPV6 , or both. AWS_INSTANCE_PORT__ If the service includes an SRV record, the value that you want Route 53 to return for the port. If the service includes HealthCheckConfig , the port on the endpoint that you want Route 53 to send requests to. This value is required if you specified settings for an SRV record when you created the service.

iId :: Lens' Instance Text Source #

An identifier that you want to associate with the instance. Note the following: * If the service that is specified by ServiceId includes settings for an SRV record, the value of InstanceId is automatically included as part of the value for the SRV record. For more information, see 'DnsRecord$Type' . * You can use this value to update an existing instance. * To register a new instance, you must specify a value that is unique among instances that you register by using the same service. * If you specify an existing InstanceId and ServiceId , Route 53 updates the existing records. If there's also an existing health check, Route 53 deletes the old health check and creates a new one.

InstanceSummary

data InstanceSummary Source #

A complex type that contains information about the instances that you registered by using a specified service.

See: instanceSummary smart constructor.

Instances
Eq InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: InstanceSummary -> Constr #

dataTypeOf :: InstanceSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep InstanceSummary :: Type -> Type #

Hashable InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: InstanceSummary -> () #

type Rep InstanceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep InstanceSummary = D1 (MetaData "InstanceSummary" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "InstanceSummary'" PrefixI True) (S1 (MetaSel (Just "_isAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text))) :*: S1 (MetaSel (Just "_isId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

instanceSummary :: InstanceSummary Source #

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

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

  • isAttributes - A string map that contains the following information: * The attributes that are associate with the instance. * For each attribute, the applicable value. Supported attribute keys include the following: * AWS_ALIAS_DNS_NAME : For an alias record that routes traffic to an Elastic Load Balancing load balancer, the DNS name that is associated with the load balancer. * AWS_INSTANCE_CNAME : For a CNAME record, the domain name that Route 53 returns in response to DNS queries, for example, example.com . * AWS_INSTANCE_IPV4 : For an A record, the IPv4 address that Route 53 returns in response to DNS queries, for example, 192.0.2.44 . * AWS_INSTANCE_IPV6 : For an AAAA record, the IPv6 address that Route 53 returns in response to DNS queries, for example, 2001:0db8:85a3:0000:0000:abcd:0001:2345 . * AWS_INSTANCE_PORT : For an SRV record, the value that Route 53 returns for the port. In addition, if the service includes HealthCheckConfig , the port on the endpoint that Route 53 sends requests to.
  • isId - The ID for an instance that you created by using a specified service.

isAttributes :: Lens' InstanceSummary (HashMap Text Text) Source #

A string map that contains the following information: * The attributes that are associate with the instance. * For each attribute, the applicable value. Supported attribute keys include the following: * AWS_ALIAS_DNS_NAME : For an alias record that routes traffic to an Elastic Load Balancing load balancer, the DNS name that is associated with the load balancer. * AWS_INSTANCE_CNAME : For a CNAME record, the domain name that Route 53 returns in response to DNS queries, for example, example.com . * AWS_INSTANCE_IPV4 : For an A record, the IPv4 address that Route 53 returns in response to DNS queries, for example, 192.0.2.44 . * AWS_INSTANCE_IPV6 : For an AAAA record, the IPv6 address that Route 53 returns in response to DNS queries, for example, 2001:0db8:85a3:0000:0000:abcd:0001:2345 . * AWS_INSTANCE_PORT : For an SRV record, the value that Route 53 returns for the port. In addition, if the service includes HealthCheckConfig , the port on the endpoint that Route 53 sends requests to.

isId :: Lens' InstanceSummary (Maybe Text) Source #

The ID for an instance that you created by using a specified service.

Namespace

data Namespace Source #

A complex type that contains information about a specified namespace.

See: namespace smart constructor.

Instances
Eq Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: Namespace -> Constr #

dataTypeOf :: Namespace -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep Namespace :: Type -> Type #

Hashable Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: Namespace -> () #

type Rep Namespace Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

namespace :: Namespace Source #

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

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

  • nARN - The Amazon Resource Name (ARN) that Route 53 assigns to the namespace when you create it.
  • nCreatorRequestId - A unique string that identifies the request and that allows failed requests to be retried without the risk of executing an operation twice.
  • nCreateDate - The date that the namespace was created, in Unix date/time format and Coordinated Universal Time (UTC). The value of CreateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
  • nServiceCount - The number of services that are associated with the namespace.
  • nName - The name of the namespace, such as example.com .
  • nId - The ID of a namespace.
  • nType - The type of the namespace. Valid values are DNS_PUBLIC and DNS_PRIVATE .
  • nDescription - The description that you specify for the namespace when you create it.
  • nProperties - A complex type that contains information that's specific to the type of the namespace.

nARN :: Lens' Namespace (Maybe Text) Source #

The Amazon Resource Name (ARN) that Route 53 assigns to the namespace when you create it.

nCreatorRequestId :: Lens' Namespace (Maybe Text) Source #

A unique string that identifies the request and that allows failed requests to be retried without the risk of executing an operation twice.

nCreateDate :: Lens' Namespace (Maybe UTCTime) Source #

The date that the namespace was created, in Unix date/time format and Coordinated Universal Time (UTC). The value of CreateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.

nServiceCount :: Lens' Namespace (Maybe Int) Source #

The number of services that are associated with the namespace.

nName :: Lens' Namespace (Maybe Text) Source #

The name of the namespace, such as example.com .

nId :: Lens' Namespace (Maybe Text) Source #

The ID of a namespace.

nType :: Lens' Namespace (Maybe NamespaceType) Source #

The type of the namespace. Valid values are DNS_PUBLIC and DNS_PRIVATE .

nDescription :: Lens' Namespace (Maybe Text) Source #

The description that you specify for the namespace when you create it.

nProperties :: Lens' Namespace (Maybe NamespaceProperties) Source #

A complex type that contains information that's specific to the type of the namespace.

NamespaceFilter

data NamespaceFilter Source #

A complex type that identifies the namespaces that you want to list. You can choose to list public or private namespaces.

See: namespaceFilter smart constructor.

Instances
Eq NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: NamespaceFilter -> Constr #

dataTypeOf :: NamespaceFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep NamespaceFilter :: Type -> Type #

Hashable NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: NamespaceFilter -> () #

type Rep NamespaceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep NamespaceFilter = D1 (MetaData "NamespaceFilter" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "NamespaceFilter'" PrefixI True) (S1 (MetaSel (Just "_nfCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilterCondition)) :*: (S1 (MetaSel (Just "_nfName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NamespaceFilterName) :*: S1 (MetaSel (Just "_nfValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))))

namespaceFilter Source #

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

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

  • nfCondition - The operator that you want to use to determine whether ListNamespaces returns a namespace. Valid values for condition include: * EQ : When you specify EQ for the condition, you can choose to list only public namespaces or private namespaces, but not both. EQ is the default condition and can be omitted. * IN : When you specify IN for the condition, you can choose to list public namespaces, private namespaces, or both. * BETWEEN : Not applicable
  • nfName - Specify TYPE .
  • nfValues - If you specify EQ for Condition , specify either DNS_PUBLIC or DNS_PRIVATE . If you specify IN for Condition , you can specify DNS_PUBLIC , DNS_PRIVATE , or both.

nfCondition :: Lens' NamespaceFilter (Maybe FilterCondition) Source #

The operator that you want to use to determine whether ListNamespaces returns a namespace. Valid values for condition include: * EQ : When you specify EQ for the condition, you can choose to list only public namespaces or private namespaces, but not both. EQ is the default condition and can be omitted. * IN : When you specify IN for the condition, you can choose to list public namespaces, private namespaces, or both. * BETWEEN : Not applicable

nfValues :: Lens' NamespaceFilter [Text] Source #

If you specify EQ for Condition , specify either DNS_PUBLIC or DNS_PRIVATE . If you specify IN for Condition , you can specify DNS_PUBLIC , DNS_PRIVATE , or both.

NamespaceProperties

data NamespaceProperties Source #

A complex type that contains information that is specific to the namespace type.

See: namespaceProperties smart constructor.

Instances
Eq NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: NamespaceProperties -> Constr #

dataTypeOf :: NamespaceProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep NamespaceProperties :: Type -> Type #

Hashable NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: NamespaceProperties -> () #

type Rep NamespaceProperties Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep NamespaceProperties = D1 (MetaData "NamespaceProperties" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" True) (C1 (MetaCons "NamespaceProperties'" PrefixI True) (S1 (MetaSel (Just "_npDNSProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe DNSProperties))))

namespaceProperties :: NamespaceProperties Source #

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

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

  • npDNSProperties - A complex type that contains the ID for the hosted zone that Route 53 creates when you create a namespace.

npDNSProperties :: Lens' NamespaceProperties (Maybe DNSProperties) Source #

A complex type that contains the ID for the hosted zone that Route 53 creates when you create a namespace.

NamespaceSummary

data NamespaceSummary Source #

A complex type that contains information about a namespace.

See: namespaceSummary smart constructor.

Instances
Eq NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: NamespaceSummary -> Constr #

dataTypeOf :: NamespaceSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep NamespaceSummary :: Type -> Type #

Hashable NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: NamespaceSummary -> () #

type Rep NamespaceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep NamespaceSummary = D1 (MetaData "NamespaceSummary" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "NamespaceSummary'" PrefixI True) ((S1 (MetaSel (Just "_nsARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_nsId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nsType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NamespaceType)))))

namespaceSummary :: NamespaceSummary Source #

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

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

  • nsARN - The Amazon Resource Name (ARN) that Route 53 assigns to the namespace when you create it.
  • nsName - The name of the namespace. When you create a namespace, Route 53 automatically creates a hosted zone that has the same name as the namespace.
  • nsId - The ID of the namespace.
  • nsType - The type of the namespace, either public or private.

nsARN :: Lens' NamespaceSummary (Maybe Text) Source #

The Amazon Resource Name (ARN) that Route 53 assigns to the namespace when you create it.

nsName :: Lens' NamespaceSummary (Maybe Text) Source #

The name of the namespace. When you create a namespace, Route 53 automatically creates a hosted zone that has the same name as the namespace.

nsId :: Lens' NamespaceSummary (Maybe Text) Source #

The ID of the namespace.

nsType :: Lens' NamespaceSummary (Maybe NamespaceType) Source #

The type of the namespace, either public or private.

Operation

data Operation Source #

A complex type that contains information about a specified operation.

See: operation smart constructor.

Instances
Eq Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: Operation -> Constr #

dataTypeOf :: Operation -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep Operation :: Type -> Type #

Hashable Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: Operation -> () #

type Rep Operation Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

operation :: Operation Source #

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

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

  • oStatus - The status of the operation. Values include the following: * SUBMITTED : This is the initial state immediately after you submit a request. * PENDING : Route 53 is performing the operation. * SUCCESS : The operation succeeded. * FAIL : The operation failed. For the failure reason, see ErrorMessage .
  • oUpdateDate - The date and time that the value of Status changed to the current value, in Unix date/time format and Coordinated Universal Time (UTC). The value of UpdateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
  • oCreateDate - The date and time that the request was submitted, in Unix date/time format and Coordinated Universal Time (UTC). The value of CreateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
  • oTargets - The name of the target entity that is associated with the operation: * NAMESPACE : The namespace ID is returned in the ResourceId property. * SERVICE : The service ID is returned in the ResourceId property. * INSTANCE : The instance ID is returned in the ResourceId property.
  • oErrorCode - The code associated with ErrorMessage . Values for ErrorCode include the following: * ACCESS_DENIED * CANNOT_CREATE_HOSTED_ZONE * EXPIRED_TOKEN * HOSTED_ZONE_NOT_FOUND * INTERNAL_FAILURE * INVALID_CHANGE_BATCH * THROTTLED_REQUEST
  • oId - The ID of the operation that you want to get information about.
  • oType - The name of the operation that is associated with the specified ID.
  • oErrorMessage - If the value of Status is FAIL , the reason that the operation failed.

oStatus :: Lens' Operation (Maybe OperationStatus) Source #

The status of the operation. Values include the following: * SUBMITTED : This is the initial state immediately after you submit a request. * PENDING : Route 53 is performing the operation. * SUCCESS : The operation succeeded. * FAIL : The operation failed. For the failure reason, see ErrorMessage .

oUpdateDate :: Lens' Operation (Maybe UTCTime) Source #

The date and time that the value of Status changed to the current value, in Unix date/time format and Coordinated Universal Time (UTC). The value of UpdateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.

oCreateDate :: Lens' Operation (Maybe UTCTime) Source #

The date and time that the request was submitted, in Unix date/time format and Coordinated Universal Time (UTC). The value of CreateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.

oTargets :: Lens' Operation (HashMap OperationTargetType Text) Source #

The name of the target entity that is associated with the operation: * NAMESPACE : The namespace ID is returned in the ResourceId property. * SERVICE : The service ID is returned in the ResourceId property. * INSTANCE : The instance ID is returned in the ResourceId property.

oErrorCode :: Lens' Operation (Maybe Text) Source #

The code associated with ErrorMessage . Values for ErrorCode include the following: * ACCESS_DENIED * CANNOT_CREATE_HOSTED_ZONE * EXPIRED_TOKEN * HOSTED_ZONE_NOT_FOUND * INTERNAL_FAILURE * INVALID_CHANGE_BATCH * THROTTLED_REQUEST

oId :: Lens' Operation (Maybe Text) Source #

The ID of the operation that you want to get information about.

oType :: Lens' Operation (Maybe OperationType) Source #

The name of the operation that is associated with the specified ID.

oErrorMessage :: Lens' Operation (Maybe Text) Source #

If the value of Status is FAIL , the reason that the operation failed.

OperationFilter

data OperationFilter Source #

A complex type that lets you select the operations that you want to list.

See: operationFilter smart constructor.

Instances
Eq OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: OperationFilter -> Constr #

dataTypeOf :: OperationFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep OperationFilter :: Type -> Type #

Hashable OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: OperationFilter -> () #

type Rep OperationFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep OperationFilter = D1 (MetaData "OperationFilter" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "OperationFilter'" PrefixI True) (S1 (MetaSel (Just "_ofCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilterCondition)) :*: (S1 (MetaSel (Just "_ofName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OperationFilterName) :*: S1 (MetaSel (Just "_ofValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))))

operationFilter Source #

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

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

  • ofCondition - The operator that you want to use to determine whether an operation matches the specified value. Valid values for condition include: * EQ : When you specify EQ for the condition, you can specify only one value. EQ is supported for NAMESPACE_ID , SERVICE_ID , STATUS , and TYPE . EQ is the default condition and can be omitted. * IN : When you specify IN for the condition, you can specify a list of one or more values. IN is supported for STATUS and TYPE . An operation must match one of the specified values to be returned in the response. * BETWEEN : Specify a start date and an end date in Unix date/time format and Coordinated Universal Time (UTC). The start date must be the first value. BETWEEN is supported for UPDATE_DATE .
  • ofName - Specify the operations that you want to get: * NAMESPACE_ID : Gets operations related to specified namespaces. * SERVICE_ID : Gets operations related to specified services. * STATUS : Gets operations based on the status of the operations: SUBMITTED , PENDING , SUCCEED , or FAIL . * TYPE : Gets specified types of operation. * UPDATE_DATE : Gets operations that changed status during a specified date/time range.
  • ofValues - Specify values that are applicable to the value that you specify for Name : * NAMESPACE_ID : Specify one namespace ID. * SERVICE_ID : Specify one service ID. * STATUS : Specify one or more statuses: SUBMITTED , PENDING , SUCCEED , or FAIL . * TYPE : Specify one or more of the following types: CREATE_NAMESPACE , DELETE_NAMESPACE , UPDATE_SERVICE , REGISTER_INSTANCE , or DEREGISTER_INSTANCE . * UPDATE_DATE : Specify a start date and an end date in Unix date/time format and Coordinated Universal Time (UTC). The start date must be the first value.

ofCondition :: Lens' OperationFilter (Maybe FilterCondition) Source #

The operator that you want to use to determine whether an operation matches the specified value. Valid values for condition include: * EQ : When you specify EQ for the condition, you can specify only one value. EQ is supported for NAMESPACE_ID , SERVICE_ID , STATUS , and TYPE . EQ is the default condition and can be omitted. * IN : When you specify IN for the condition, you can specify a list of one or more values. IN is supported for STATUS and TYPE . An operation must match one of the specified values to be returned in the response. * BETWEEN : Specify a start date and an end date in Unix date/time format and Coordinated Universal Time (UTC). The start date must be the first value. BETWEEN is supported for UPDATE_DATE .

ofName :: Lens' OperationFilter OperationFilterName Source #

Specify the operations that you want to get: * NAMESPACE_ID : Gets operations related to specified namespaces. * SERVICE_ID : Gets operations related to specified services. * STATUS : Gets operations based on the status of the operations: SUBMITTED , PENDING , SUCCEED , or FAIL . * TYPE : Gets specified types of operation. * UPDATE_DATE : Gets operations that changed status during a specified date/time range.

ofValues :: Lens' OperationFilter [Text] Source #

Specify values that are applicable to the value that you specify for Name : * NAMESPACE_ID : Specify one namespace ID. * SERVICE_ID : Specify one service ID. * STATUS : Specify one or more statuses: SUBMITTED , PENDING , SUCCEED , or FAIL . * TYPE : Specify one or more of the following types: CREATE_NAMESPACE , DELETE_NAMESPACE , UPDATE_SERVICE , REGISTER_INSTANCE , or DEREGISTER_INSTANCE . * UPDATE_DATE : Specify a start date and an end date in Unix date/time format and Coordinated Universal Time (UTC). The start date must be the first value.

OperationSummary

data OperationSummary Source #

A complex type that contains information about an operation that matches the criteria that you specified in a ListOperations request.

See: operationSummary smart constructor.

Instances
Eq OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: OperationSummary -> Constr #

dataTypeOf :: OperationSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep OperationSummary :: Type -> Type #

Hashable OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: OperationSummary -> () #

type Rep OperationSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep OperationSummary = D1 (MetaData "OperationSummary" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "OperationSummary'" PrefixI True) (S1 (MetaSel (Just "_osStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OperationStatus)) :*: S1 (MetaSel (Just "_osId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

operationSummary :: OperationSummary Source #

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

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

  • osStatus - The status of the operation. Values include the following: * SUBMITTED : This is the initial state immediately after you submit a request. * PENDING : Route 53 is performing the operation. * SUCCESS : The operation succeeded. * FAIL : The operation failed. For the failure reason, see ErrorMessage .
  • osId - The ID for an operation.

osStatus :: Lens' OperationSummary (Maybe OperationStatus) Source #

The status of the operation. Values include the following: * SUBMITTED : This is the initial state immediately after you submit a request. * PENDING : Route 53 is performing the operation. * SUCCESS : The operation succeeded. * FAIL : The operation failed. For the failure reason, see ErrorMessage .

osId :: Lens' OperationSummary (Maybe Text) Source #

The ID for an operation.

ServiceChange

data ServiceChange Source #

A complex type that contains changes to an existing service.

See: serviceChange smart constructor.

Instances
Eq ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: ServiceChange -> Constr #

dataTypeOf :: ServiceChange -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep ServiceChange :: Type -> Type #

Hashable ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: ServiceChange -> () #

type Rep ServiceChange Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep ServiceChange = D1 (MetaData "ServiceChange" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "ServiceChange'" PrefixI True) (S1 (MetaSel (Just "_scHealthCheckConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HealthCheckConfig)) :*: (S1 (MetaSel (Just "_scDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_scDNSConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DNSConfigChange))))

serviceChange Source #

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

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

  • scHealthCheckConfig - Undocumented member.
  • scDescription - A description for the service.
  • scDNSConfig - A complex type that contains information about the records that you want Route 53 to create when you register an instance.

scDescription :: Lens' ServiceChange (Maybe Text) Source #

A description for the service.

scDNSConfig :: Lens' ServiceChange DNSConfigChange Source #

A complex type that contains information about the records that you want Route 53 to create when you register an instance.

ServiceFilter

data ServiceFilter Source #

A complex type that lets you specify the namespaces that you want to list services for.

See: serviceFilter smart constructor.

Instances
Eq ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: ServiceFilter -> Constr #

dataTypeOf :: ServiceFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep ServiceFilter :: Type -> Type #

Hashable ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

ToJSON ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: ServiceFilter -> () #

type Rep ServiceFilter Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep ServiceFilter = D1 (MetaData "ServiceFilter" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "ServiceFilter'" PrefixI True) (S1 (MetaSel (Just "_sfCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilterCondition)) :*: (S1 (MetaSel (Just "_sfName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ServiceFilterName) :*: S1 (MetaSel (Just "_sfValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))))

serviceFilter Source #

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

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

  • sfCondition - The operator that you want to use to determine whether a service is returned by ListServices . Valid values for Condition include the following: * EQ : When you specify EQ , specify one namespace ID for Values . EQ is the default condition and can be omitted. * IN : When you specify IN , specify a list of the IDs for the namespaces that you want ListServices to return a list of services for. * BETWEEN : Not applicable.
  • sfName - Specify NAMESPACE_ID .
  • sfValues - The values that are applicable to the value that you specify for Condition to filter the list of services.

sfCondition :: Lens' ServiceFilter (Maybe FilterCondition) Source #

The operator that you want to use to determine whether a service is returned by ListServices . Valid values for Condition include the following: * EQ : When you specify EQ , specify one namespace ID for Values . EQ is the default condition and can be omitted. * IN : When you specify IN , specify a list of the IDs for the namespaces that you want ListServices to return a list of services for. * BETWEEN : Not applicable.

sfValues :: Lens' ServiceFilter [Text] Source #

The values that are applicable to the value that you specify for Condition to filter the list of services.

ServiceInfo

data ServiceInfo Source #

A complex type that contains information about the specified service.

See: serviceInfo smart constructor.

Instances
Eq ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: ServiceInfo -> Constr #

dataTypeOf :: ServiceInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep ServiceInfo :: Type -> Type #

Hashable ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: ServiceInfo -> () #

type Rep ServiceInfo Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

serviceInfo :: ServiceInfo Source #

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

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

  • siInstanceCount - The number of instances that are currently associated with the service. Instances that were previously associated with the service but that have been deleted are not included in the count.
  • siARN - The Amazon Resource Name (ARN) that Route 53 assigns to the service when you create it.
  • siHealthCheckConfig - Public DNS namespaces only. A complex type that contains settings for an optional health check. If you specify settings for a health check, Route 53 associates the health check with all the records that you specify in DnsConfig . For information about the charges for health checks, see Route 53 Pricing .
  • siCreatorRequestId - A unique string that identifies the request and that allows failed requests to be retried without the risk of executing the operation twice. CreatorRequestId can be any unique string, for example, a date/time stamp.
  • siCreateDate - The date and time that the service was created, in Unix format and Coordinated Universal Time (UTC). The value of CreateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.
  • siHealthCheckCustomConfig - Undocumented member.
  • siName - The name of the service.
  • siId - The ID that Route 53 assigned to the service when you created it.
  • siDNSConfig - A complex type that contains information about the records that you want Route 53 to create when you register an instance.
  • siDescription - The description of the service.

siInstanceCount :: Lens' ServiceInfo (Maybe Int) Source #

The number of instances that are currently associated with the service. Instances that were previously associated with the service but that have been deleted are not included in the count.

siARN :: Lens' ServiceInfo (Maybe Text) Source #

The Amazon Resource Name (ARN) that Route 53 assigns to the service when you create it.

siHealthCheckConfig :: Lens' ServiceInfo (Maybe HealthCheckConfig) Source #

Public DNS namespaces only. A complex type that contains settings for an optional health check. If you specify settings for a health check, Route 53 associates the health check with all the records that you specify in DnsConfig . For information about the charges for health checks, see Route 53 Pricing .

siCreatorRequestId :: Lens' ServiceInfo (Maybe Text) Source #

A unique string that identifies the request and that allows failed requests to be retried without the risk of executing the operation twice. CreatorRequestId can be any unique string, for example, a date/time stamp.

siCreateDate :: Lens' ServiceInfo (Maybe UTCTime) Source #

The date and time that the service was created, in Unix format and Coordinated Universal Time (UTC). The value of CreateDate is accurate to milliseconds. For example, the value 1516925490.087 represents Friday, January 26, 2018 12:11:30.087 AM.

siName :: Lens' ServiceInfo (Maybe Text) Source #

The name of the service.

siId :: Lens' ServiceInfo (Maybe Text) Source #

The ID that Route 53 assigned to the service when you created it.

siDNSConfig :: Lens' ServiceInfo (Maybe DNSConfig) Source #

A complex type that contains information about the records that you want Route 53 to create when you register an instance.

siDescription :: Lens' ServiceInfo (Maybe Text) Source #

The description of the service.

ServiceSummary

data ServiceSummary Source #

A complex type that contains information about a specified service.

See: serviceSummary smart constructor.

Instances
Eq ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Data ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

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

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

toConstr :: ServiceSummary -> Constr #

dataTypeOf :: ServiceSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Show ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Generic ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Associated Types

type Rep ServiceSummary :: Type -> Type #

Hashable ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

FromJSON ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

NFData ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

Methods

rnf :: ServiceSummary -> () #

type Rep ServiceSummary Source # 
Instance details

Defined in Network.AWS.Route53AutoNaming.Types.Product

type Rep ServiceSummary = D1 (MetaData "ServiceSummary" "Network.AWS.Route53AutoNaming.Types.Product" "amazonka-route53-autonaming-1.6.1-6b8id7oIY1vC1CYd7O7Vs3" False) (C1 (MetaCons "ServiceSummary'" PrefixI True) ((S1 (MetaSel (Just "_ssInstanceCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_ssARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_ssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_ssId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ssDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

serviceSummary :: ServiceSummary Source #

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

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

  • ssInstanceCount - The number of instances that are currently associated with the service. Instances that were previously associated with the service but that have been deleted are not included in the count.
  • ssARN - The Amazon Resource Name (ARN) that Route 53 assigns to the service when you create it.
  • ssName - The name of the service.
  • ssId - The ID that Route 53 assigned to the service when you created it.
  • ssDescription - The description that you specify when you create the service.

ssInstanceCount :: Lens' ServiceSummary (Maybe Int) Source #

The number of instances that are currently associated with the service. Instances that were previously associated with the service but that have been deleted are not included in the count.

ssARN :: Lens' ServiceSummary (Maybe Text) Source #

The Amazon Resource Name (ARN) that Route 53 assigns to the service when you create it.

ssName :: Lens' ServiceSummary (Maybe Text) Source #

The name of the service.

ssId :: Lens' ServiceSummary (Maybe Text) Source #

The ID that Route 53 assigned to the service when you created it.

ssDescription :: Lens' ServiceSummary (Maybe Text) Source #

The description that you specify when you create the service.