amazonka-ds-1.4.3: Amazon Directory Service SDK.

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

Network.AWS.DirectoryService

Contents

Description

AWS Directory Service

This is the AWS Directory Service API Reference. This guide provides detailed information about AWS Directory Service operations, data types, parameters, and errors.

Synopsis

Service Configuration

directoryService :: Service Source #

API version '2015-04-16' of the Amazon Directory Service SDK configuration.

Errors

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

DirectoryUnavailableException

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

The specified directory is unavailable or could not be found.

AuthenticationFailedException

InvalidParameterException

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

One or more parameters are not valid.

UnsupportedOperationException

EntityAlreadyExistsException

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

The specified entity already exists.

DirectoryLimitExceededException

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

The maximum number of directories in the region has been reached. You can use the GetDirectoryLimits operation to determine your directory limits in the region.

EntityDoesNotExistException

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

The specified entity could not be found.

InsufficientPermissionsException

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

The account does not have sufficient permission to perform the operation.

InvalidNextTokenException

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

The NextToken value is not valid.

ServiceException

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

An exception has occurred in AWS Directory Service.

SnapshotLimitExceededException

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

The maximum number of manual snapshots for the directory has been reached. You can use the GetSnapshotLimits operation to determine the snapshot limits for a directory.

ClientException

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

A client exception has occurred.

Waiters

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

Operations

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

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

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

DescribeConditionalForwarders

GetSnapshotLimits

RegisterEventTopic

ConnectDirectory

CreateAlias

DescribeDirectories

DescribeTrusts

DeleteTrust

CreateMicrosoftAD

DeregisterEventTopic

CreateDirectory

DescribeEventTopics

UpdateConditionalForwarder

DeleteConditionalForwarder

EnableSSO

EnableRadius

DisableRadius

RestoreFromSnapshot

DescribeSnapshots

DeleteSnapshot

CreateTrust

DeleteDirectory

CreateSnapshot

CreateComputer

DisableSSO

VerifyTrust

CreateConditionalForwarder

GetDirectoryLimits

UpdateRadius

Types

DirectorySize

data DirectorySize Source #

Constructors

Large 
Small 

Instances

Bounded DirectorySize Source # 
Enum DirectorySize Source # 
Eq DirectorySize Source # 
Data DirectorySize Source # 

Methods

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

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

toConstr :: DirectorySize -> Constr #

dataTypeOf :: DirectorySize -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DirectorySize Source # 
Read DirectorySize Source # 
Show DirectorySize Source # 
Generic DirectorySize Source # 

Associated Types

type Rep DirectorySize :: * -> * #

ToJSON DirectorySize Source # 
FromJSON DirectorySize Source # 
Hashable DirectorySize Source # 
NFData DirectorySize Source # 

Methods

rnf :: DirectorySize -> () #

ToHeader DirectorySize Source # 
ToQuery DirectorySize Source # 
ToByteString DirectorySize Source # 
FromText DirectorySize Source # 
ToText DirectorySize Source # 

Methods

toText :: DirectorySize -> Text #

type Rep DirectorySize Source # 
type Rep DirectorySize = D1 (MetaData "DirectorySize" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) (C1 (MetaCons "Large" PrefixI False) U1) (C1 (MetaCons "Small" PrefixI False) U1))

DirectoryStage

data DirectoryStage Source #

Instances

Bounded DirectoryStage Source # 
Enum DirectoryStage Source # 
Eq DirectoryStage Source # 
Data DirectoryStage Source # 

Methods

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

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

toConstr :: DirectoryStage -> Constr #

dataTypeOf :: DirectoryStage -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DirectoryStage Source # 
Read DirectoryStage Source # 
Show DirectoryStage Source # 
Generic DirectoryStage Source # 

Associated Types

type Rep DirectoryStage :: * -> * #

FromJSON DirectoryStage Source # 
Hashable DirectoryStage Source # 
NFData DirectoryStage Source # 

Methods

rnf :: DirectoryStage -> () #

ToHeader DirectoryStage Source # 
ToQuery DirectoryStage Source # 
ToByteString DirectoryStage Source # 
FromText DirectoryStage Source # 
ToText DirectoryStage Source # 
type Rep DirectoryStage Source # 
type Rep DirectoryStage = D1 (MetaData "DirectoryStage" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DSActive" PrefixI False) U1) (C1 (MetaCons "DSCreated" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DSCreating" PrefixI False) U1) ((:+:) (C1 (MetaCons "DSDeleted" PrefixI False) U1) (C1 (MetaCons "DSDeleting" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "DSFailed" PrefixI False) U1) ((:+:) (C1 (MetaCons "DSImpaired" PrefixI False) U1) (C1 (MetaCons "DSInoperable" PrefixI False) U1))) ((:+:) (C1 (MetaCons "DSRequested" PrefixI False) U1) ((:+:) (C1 (MetaCons "DSRestoreFailed" PrefixI False) U1) (C1 (MetaCons "DSRestoring" PrefixI False) U1)))))

DirectoryType

data DirectoryType Source #

Instances

Bounded DirectoryType Source # 
Enum DirectoryType Source # 
Eq DirectoryType Source # 
Data DirectoryType Source # 

Methods

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

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

toConstr :: DirectoryType -> Constr #

dataTypeOf :: DirectoryType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DirectoryType Source # 
Read DirectoryType Source # 
Show DirectoryType Source # 
Generic DirectoryType Source # 

Associated Types

type Rep DirectoryType :: * -> * #

FromJSON DirectoryType Source # 
Hashable DirectoryType Source # 
NFData DirectoryType Source # 

Methods

rnf :: DirectoryType -> () #

ToHeader DirectoryType Source # 
ToQuery DirectoryType Source # 
ToByteString DirectoryType Source # 
FromText DirectoryType Source # 
ToText DirectoryType Source # 

Methods

toText :: DirectoryType -> Text #

type Rep DirectoryType Source # 
type Rep DirectoryType = D1 (MetaData "DirectoryType" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) (C1 (MetaCons "ADConnector" PrefixI False) U1) ((:+:) (C1 (MetaCons "MicrosoftAD" PrefixI False) U1) (C1 (MetaCons "SimpleAD" PrefixI False) U1)))

RadiusAuthenticationProtocol

data RadiusAuthenticationProtocol Source #

Constructors

Chap 
MsCHAPV1 
MsCHAPV2 
Pap 

Instances

Bounded RadiusAuthenticationProtocol Source # 
Enum RadiusAuthenticationProtocol Source # 
Eq RadiusAuthenticationProtocol Source # 
Data RadiusAuthenticationProtocol Source # 

Methods

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

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

toConstr :: RadiusAuthenticationProtocol -> Constr #

dataTypeOf :: RadiusAuthenticationProtocol -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RadiusAuthenticationProtocol Source # 
Read RadiusAuthenticationProtocol Source # 
Show RadiusAuthenticationProtocol Source # 
Generic RadiusAuthenticationProtocol Source # 
ToJSON RadiusAuthenticationProtocol Source # 
FromJSON RadiusAuthenticationProtocol Source # 
Hashable RadiusAuthenticationProtocol Source # 
NFData RadiusAuthenticationProtocol Source # 
ToHeader RadiusAuthenticationProtocol Source # 
ToQuery RadiusAuthenticationProtocol Source # 
ToByteString RadiusAuthenticationProtocol Source # 
FromText RadiusAuthenticationProtocol Source # 
ToText RadiusAuthenticationProtocol Source # 
type Rep RadiusAuthenticationProtocol Source # 
type Rep RadiusAuthenticationProtocol = D1 (MetaData "RadiusAuthenticationProtocol" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) ((:+:) (C1 (MetaCons "Chap" PrefixI False) U1) (C1 (MetaCons "MsCHAPV1" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MsCHAPV2" PrefixI False) U1) (C1 (MetaCons "Pap" PrefixI False) U1)))

RadiusStatus

data RadiusStatus Source #

Constructors

Completed 
Creating 
Failed 

Instances

Bounded RadiusStatus Source # 
Enum RadiusStatus Source # 
Eq RadiusStatus Source # 
Data RadiusStatus Source # 

Methods

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

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

toConstr :: RadiusStatus -> Constr #

dataTypeOf :: RadiusStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RadiusStatus Source # 
Read RadiusStatus Source # 
Show RadiusStatus Source # 
Generic RadiusStatus Source # 

Associated Types

type Rep RadiusStatus :: * -> * #

FromJSON RadiusStatus Source # 
Hashable RadiusStatus Source # 
NFData RadiusStatus Source # 

Methods

rnf :: RadiusStatus -> () #

ToHeader RadiusStatus Source # 
ToQuery RadiusStatus Source # 
ToByteString RadiusStatus Source # 
FromText RadiusStatus Source # 
ToText RadiusStatus Source # 

Methods

toText :: RadiusStatus -> Text #

type Rep RadiusStatus Source # 
type Rep RadiusStatus = D1 (MetaData "RadiusStatus" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) (C1 (MetaCons "Completed" PrefixI False) U1) ((:+:) (C1 (MetaCons "Creating" PrefixI False) U1) (C1 (MetaCons "Failed" PrefixI False) U1)))

ReplicationScope

data ReplicationScope Source #

Constructors

Domain 

Instances

Bounded ReplicationScope Source # 
Enum ReplicationScope Source # 
Eq ReplicationScope Source # 
Data ReplicationScope Source # 

Methods

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

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

toConstr :: ReplicationScope -> Constr #

dataTypeOf :: ReplicationScope -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReplicationScope Source # 
Read ReplicationScope Source # 
Show ReplicationScope Source # 
Generic ReplicationScope Source # 
FromJSON ReplicationScope Source # 
Hashable ReplicationScope Source # 
NFData ReplicationScope Source # 

Methods

rnf :: ReplicationScope -> () #

ToHeader ReplicationScope Source # 
ToQuery ReplicationScope Source # 
ToByteString ReplicationScope Source # 
FromText ReplicationScope Source # 
ToText ReplicationScope Source # 
type Rep ReplicationScope Source # 
type Rep ReplicationScope = D1 (MetaData "ReplicationScope" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "Domain" PrefixI False) U1)

SnapshotStatus

data SnapshotStatus Source #

Instances

Bounded SnapshotStatus Source # 
Enum SnapshotStatus Source # 
Eq SnapshotStatus Source # 
Data SnapshotStatus Source # 

Methods

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

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

toConstr :: SnapshotStatus -> Constr #

dataTypeOf :: SnapshotStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SnapshotStatus Source # 
Read SnapshotStatus Source # 
Show SnapshotStatus Source # 
Generic SnapshotStatus Source # 

Associated Types

type Rep SnapshotStatus :: * -> * #

FromJSON SnapshotStatus Source # 
Hashable SnapshotStatus Source # 
NFData SnapshotStatus Source # 

Methods

rnf :: SnapshotStatus -> () #

ToHeader SnapshotStatus Source # 
ToQuery SnapshotStatus Source # 
ToByteString SnapshotStatus Source # 
FromText SnapshotStatus Source # 
ToText SnapshotStatus Source # 
type Rep SnapshotStatus Source # 
type Rep SnapshotStatus = D1 (MetaData "SnapshotStatus" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) (C1 (MetaCons "SSCompleted" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSCreating" PrefixI False) U1) (C1 (MetaCons "SSFailed" PrefixI False) U1)))

SnapshotType

data SnapshotType Source #

Constructors

Auto 
Manual 

Instances

Bounded SnapshotType Source # 
Enum SnapshotType Source # 
Eq SnapshotType Source # 
Data SnapshotType Source # 

Methods

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

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

toConstr :: SnapshotType -> Constr #

dataTypeOf :: SnapshotType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SnapshotType Source # 
Read SnapshotType Source # 
Show SnapshotType Source # 
Generic SnapshotType Source # 

Associated Types

type Rep SnapshotType :: * -> * #

FromJSON SnapshotType Source # 
Hashable SnapshotType Source # 
NFData SnapshotType Source # 

Methods

rnf :: SnapshotType -> () #

ToHeader SnapshotType Source # 
ToQuery SnapshotType Source # 
ToByteString SnapshotType Source # 
FromText SnapshotType Source # 
ToText SnapshotType Source # 

Methods

toText :: SnapshotType -> Text #

type Rep SnapshotType Source # 
type Rep SnapshotType = D1 (MetaData "SnapshotType" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) (C1 (MetaCons "Auto" PrefixI False) U1) (C1 (MetaCons "Manual" PrefixI False) U1))

TopicStatus

data TopicStatus Source #

Instances

Bounded TopicStatus Source # 
Enum TopicStatus Source # 
Eq TopicStatus Source # 
Data TopicStatus Source # 

Methods

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

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

toConstr :: TopicStatus -> Constr #

dataTypeOf :: TopicStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TopicStatus Source # 
Read TopicStatus Source # 
Show TopicStatus Source # 
Generic TopicStatus Source # 

Associated Types

type Rep TopicStatus :: * -> * #

FromJSON TopicStatus Source # 
Hashable TopicStatus Source # 
NFData TopicStatus Source # 

Methods

rnf :: TopicStatus -> () #

ToHeader TopicStatus Source # 
ToQuery TopicStatus Source # 
ToByteString TopicStatus Source # 
FromText TopicStatus Source # 
ToText TopicStatus Source # 

Methods

toText :: TopicStatus -> Text #

type Rep TopicStatus Source # 
type Rep TopicStatus = D1 (MetaData "TopicStatus" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) ((:+:) (C1 (MetaCons "TDeleted" PrefixI False) U1) (C1 (MetaCons "TFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TRegistered" PrefixI False) U1) (C1 (MetaCons "TTopicNotFound" PrefixI False) U1)))

TrustDirection

data TrustDirection Source #

Instances

Bounded TrustDirection Source # 
Enum TrustDirection Source # 
Eq TrustDirection Source # 
Data TrustDirection Source # 

Methods

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

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

toConstr :: TrustDirection -> Constr #

dataTypeOf :: TrustDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrustDirection Source # 
Read TrustDirection Source # 
Show TrustDirection Source # 
Generic TrustDirection Source # 

Associated Types

type Rep TrustDirection :: * -> * #

ToJSON TrustDirection Source # 
FromJSON TrustDirection Source # 
Hashable TrustDirection Source # 
NFData TrustDirection Source # 

Methods

rnf :: TrustDirection -> () #

ToHeader TrustDirection Source # 
ToQuery TrustDirection Source # 
ToByteString TrustDirection Source # 
FromText TrustDirection Source # 
ToText TrustDirection Source # 
type Rep TrustDirection Source # 
type Rep TrustDirection = D1 (MetaData "TrustDirection" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) (C1 (MetaCons "OneWayIncoming" PrefixI False) U1) ((:+:) (C1 (MetaCons "OneWayOutgoing" PrefixI False) U1) (C1 (MetaCons "TwoWay" PrefixI False) U1)))

TrustState

data TrustState Source #

Instances

Bounded TrustState Source # 
Enum TrustState Source # 
Eq TrustState Source # 
Data TrustState Source # 

Methods

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

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

toConstr :: TrustState -> Constr #

dataTypeOf :: TrustState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrustState Source # 
Read TrustState Source # 
Show TrustState Source # 
Generic TrustState Source # 

Associated Types

type Rep TrustState :: * -> * #

FromJSON TrustState Source # 
Hashable TrustState Source # 
NFData TrustState Source # 

Methods

rnf :: TrustState -> () #

ToHeader TrustState Source # 
ToQuery TrustState Source # 
ToByteString TrustState Source # 
FromText TrustState Source # 
ToText TrustState Source # 

Methods

toText :: TrustState -> Text #

type Rep TrustState Source # 
type Rep TrustState = D1 (MetaData "TrustState" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TSCreated" PrefixI False) U1) (C1 (MetaCons "TSCreating" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TSDeleted" PrefixI False) U1) (C1 (MetaCons "TSDeleting" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "TSFailed" PrefixI False) U1) (C1 (MetaCons "TSVerified" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TSVerifyFailed" PrefixI False) U1) (C1 (MetaCons "TSVerifying" PrefixI False) U1))))

TrustType

data TrustType Source #

Constructors

Forest 

Instances

Bounded TrustType Source # 
Enum TrustType Source # 
Eq TrustType Source # 
Data TrustType Source # 

Methods

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

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

toConstr :: TrustType -> Constr #

dataTypeOf :: TrustType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrustType Source # 
Read TrustType Source # 
Show TrustType Source # 
Generic TrustType Source # 

Associated Types

type Rep TrustType :: * -> * #

ToJSON TrustType Source # 
FromJSON TrustType Source # 
Hashable TrustType Source # 
NFData TrustType Source # 

Methods

rnf :: TrustType -> () #

ToHeader TrustType Source # 
ToQuery TrustType Source # 
ToByteString TrustType Source # 

Methods

toBS :: TrustType -> ByteString #

FromText TrustType Source # 
ToText TrustType Source # 

Methods

toText :: TrustType -> Text #

type Rep TrustType Source # 
type Rep TrustType = D1 (MetaData "TrustType" "Network.AWS.DirectoryService.Types.Sum" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "Forest" PrefixI False) U1)

Attribute

data Attribute Source #

Represents a named directory attribute.

See: attribute smart constructor.

Instances

Eq Attribute Source # 
Data Attribute Source # 

Methods

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

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

toConstr :: Attribute -> Constr #

dataTypeOf :: Attribute -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Attribute Source # 
Show Attribute Source # 
Generic Attribute Source # 

Associated Types

type Rep Attribute :: * -> * #

ToJSON Attribute Source # 
FromJSON Attribute Source # 
Hashable Attribute Source # 
NFData Attribute Source # 

Methods

rnf :: Attribute -> () #

type Rep Attribute Source # 
type Rep Attribute = D1 (MetaData "Attribute" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "Attribute'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

attribute :: Attribute Source #

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

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

aValue :: Lens' Attribute (Maybe Text) Source #

The value of the attribute.

aName :: Lens' Attribute (Maybe Text) Source #

The name of the attribute.

Computer

data Computer Source #

Contains information about a computer account in a directory.

See: computer smart constructor.

Instances

Eq Computer Source # 
Data Computer Source # 

Methods

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

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

toConstr :: Computer -> Constr #

dataTypeOf :: Computer -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Computer Source # 
Show Computer Source # 
Generic Computer Source # 

Associated Types

type Rep Computer :: * -> * #

Methods

from :: Computer -> Rep Computer x #

to :: Rep Computer x -> Computer #

FromJSON Computer Source # 
Hashable Computer Source # 

Methods

hashWithSalt :: Int -> Computer -> Int #

hash :: Computer -> Int #

NFData Computer Source # 

Methods

rnf :: Computer -> () #

type Rep Computer Source # 
type Rep Computer = D1 (MetaData "Computer" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "Computer'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cComputerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cComputerAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Attribute]))) (S1 (MetaSel (Just Symbol "_cComputerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

computer :: Computer Source #

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

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

cComputerId :: Lens' Computer (Maybe Text) Source #

The identifier of the computer.

cComputerAttributes :: Lens' Computer [Attribute] Source #

An array of Attribute objects containing the LDAP attributes that belong to the computer account.

cComputerName :: Lens' Computer (Maybe Text) Source #

The computer name.

ConditionalForwarder

data ConditionalForwarder Source #

Points to a remote domain with which you are setting up a trust relationship. Conditional forwarders are required in order to set up a trust relationship with another domain.

See: conditionalForwarder smart constructor.

Instances

Eq ConditionalForwarder Source # 
Data ConditionalForwarder Source # 

Methods

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

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

toConstr :: ConditionalForwarder -> Constr #

dataTypeOf :: ConditionalForwarder -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ConditionalForwarder Source # 
Show ConditionalForwarder Source # 
Generic ConditionalForwarder Source # 
FromJSON ConditionalForwarder Source # 
Hashable ConditionalForwarder Source # 
NFData ConditionalForwarder Source # 

Methods

rnf :: ConditionalForwarder -> () #

type Rep ConditionalForwarder Source # 
type Rep ConditionalForwarder = D1 (MetaData "ConditionalForwarder" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "ConditionalForwarder'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cfDNSIPAddrs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_cfRemoteDomainName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cfReplicationScope") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReplicationScope))))))

conditionalForwarder :: ConditionalForwarder Source #

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

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

cfDNSIPAddrs :: Lens' ConditionalForwarder [Text] Source #

The IP addresses of the remote DNS server associated with RemoteDomainName. This is the IP address of the DNS server that your conditional forwarder points to.

cfRemoteDomainName :: Lens' ConditionalForwarder (Maybe Text) Source #

The fully qualified domain name (FQDN) of the remote domains pointed to by the conditional forwarder.

cfReplicationScope :: Lens' ConditionalForwarder (Maybe ReplicationScope) Source #

The replication scope of the conditional forwarder. The only allowed value is Domain, which will replicate the conditional forwarder to all of the domain controllers for your AWS directory.

DirectoryConnectSettings

data DirectoryConnectSettings Source #

Contains information for the ConnectDirectory operation when an AD Connector directory is being created.

See: directoryConnectSettings smart constructor.

Instances

Eq DirectoryConnectSettings Source # 
Data DirectoryConnectSettings Source # 

Methods

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

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

toConstr :: DirectoryConnectSettings -> Constr #

dataTypeOf :: DirectoryConnectSettings -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DirectoryConnectSettings Source # 
Show DirectoryConnectSettings Source # 
Generic DirectoryConnectSettings Source # 
ToJSON DirectoryConnectSettings Source # 
Hashable DirectoryConnectSettings Source # 
NFData DirectoryConnectSettings Source # 
type Rep DirectoryConnectSettings Source # 
type Rep DirectoryConnectSettings = D1 (MetaData "DirectoryConnectSettings" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "DirectoryConnectSettings'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dcsVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dcsSubnetIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_dcsCustomerDNSIPs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text])) (S1 (MetaSel (Just Symbol "_dcsCustomerUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

directoryConnectSettings Source #

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

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

dcsVPCId :: Lens' DirectoryConnectSettings Text Source #

The identifier of the VPC in which the AD Connector is created.

dcsSubnetIds :: Lens' DirectoryConnectSettings [Text] Source #

A list of subnet identifiers in the VPC in which the AD Connector is created.

dcsCustomerDNSIPs :: Lens' DirectoryConnectSettings [Text] Source #

A list of one or more IP addresses of DNS servers or domain controllers in the on-premises directory.

dcsCustomerUserName :: Lens' DirectoryConnectSettings Text Source #

The username of an account in the on-premises directory that is used to connect to the directory. This account must have the following privileges:

  • Read users and groups
  • Create computer objects
  • Join computers to the domain

DirectoryConnectSettingsDescription

data DirectoryConnectSettingsDescription Source #

Contains information about an AD Connector directory.

See: directoryConnectSettingsDescription smart constructor.

Instances

Eq DirectoryConnectSettingsDescription Source # 
Data DirectoryConnectSettingsDescription Source # 

Methods

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

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

toConstr :: DirectoryConnectSettingsDescription -> Constr #

dataTypeOf :: DirectoryConnectSettingsDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DirectoryConnectSettingsDescription Source # 
Show DirectoryConnectSettingsDescription Source # 
Generic DirectoryConnectSettingsDescription Source # 
FromJSON DirectoryConnectSettingsDescription Source # 
Hashable DirectoryConnectSettingsDescription Source # 
NFData DirectoryConnectSettingsDescription Source # 
type Rep DirectoryConnectSettingsDescription Source # 
type Rep DirectoryConnectSettingsDescription = D1 (MetaData "DirectoryConnectSettingsDescription" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "DirectoryConnectSettingsDescription'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dcsdCustomerUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_dcsdSubnetIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_dcsdVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_dcsdSecurityGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_dcsdConnectIPs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_dcsdAvailabilityZones") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))))

directoryConnectSettingsDescription :: DirectoryConnectSettingsDescription Source #

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

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

dcsdCustomerUserName :: Lens' DirectoryConnectSettingsDescription (Maybe Text) Source #

The username of the service account in the on-premises directory.

dcsdSubnetIds :: Lens' DirectoryConnectSettingsDescription [Text] Source #

A list of subnet identifiers in the VPC that the AD connector is in.

dcsdVPCId :: Lens' DirectoryConnectSettingsDescription (Maybe Text) Source #

The identifier of the VPC that the AD Connector is in.

dcsdSecurityGroupId :: Lens' DirectoryConnectSettingsDescription (Maybe Text) Source #

The security group identifier for the AD Connector directory.

dcsdConnectIPs :: Lens' DirectoryConnectSettingsDescription [Text] Source #

The IP addresses of the AD Connector servers.

dcsdAvailabilityZones :: Lens' DirectoryConnectSettingsDescription [Text] Source #

A list of the Availability Zones that the directory is in.

DirectoryDescription

data DirectoryDescription Source #

Contains information about an AWS Directory Service directory.

See: directoryDescription smart constructor.

Instances

Eq DirectoryDescription Source # 
Data DirectoryDescription Source # 

Methods

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

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

toConstr :: DirectoryDescription -> Constr #

dataTypeOf :: DirectoryDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DirectoryDescription Source # 
Show DirectoryDescription Source # 
Generic DirectoryDescription Source # 
FromJSON DirectoryDescription Source # 
Hashable DirectoryDescription Source # 
NFData DirectoryDescription Source # 

Methods

rnf :: DirectoryDescription -> () #

type Rep DirectoryDescription Source # 
type Rep DirectoryDescription = D1 (MetaData "DirectoryDescription" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "DirectoryDescription'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ddRadiusStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RadiusStatus))) (S1 (MetaSel (Just Symbol "_ddStage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectoryStage)))) ((:*:) (S1 (MetaSel (Just Symbol "_ddDirectoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ddAccessURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ddShortName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ddSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectorySize)))) ((:*:) (S1 (MetaSel (Just Symbol "_ddRadiusSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RadiusSettings))) ((:*:) (S1 (MetaSel (Just Symbol "_ddLaunchTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) (S1 (MetaSel (Just Symbol "_ddAlias") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ddName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ddStageLastUpdatedDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))) ((:*:) (S1 (MetaSel (Just Symbol "_ddSSOEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ddDNSIPAddrs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ddVPCSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectoryVPCSettingsDescription))) (S1 (MetaSel (Just Symbol "_ddType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectoryType)))) ((:*:) (S1 (MetaSel (Just Symbol "_ddStageReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ddConnectSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectoryConnectSettingsDescription))) (S1 (MetaSel (Just Symbol "_ddDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

ddRadiusStatus :: Lens' DirectoryDescription (Maybe RadiusStatus) Source #

The status of the RADIUS MFA server connection.

ddStage :: Lens' DirectoryDescription (Maybe DirectoryStage) Source #

The current stage of the directory.

ddDirectoryId :: Lens' DirectoryDescription (Maybe Text) Source #

The directory identifier.

ddAccessURL :: Lens' DirectoryDescription (Maybe Text) Source #

The access URL for the directory, such as 'http://<alias>.awsapps.com'. If no alias has been created for the directory, '<alias>' is the directory identifier, such as 'd-XXXXXXXXXX'.

ddShortName :: Lens' DirectoryDescription (Maybe Text) Source #

The short name of the directory.

ddRadiusSettings :: Lens' DirectoryDescription (Maybe RadiusSettings) Source #

A RadiusSettings object that contains information about the RADIUS server configured for this directory.

ddLaunchTime :: Lens' DirectoryDescription (Maybe UTCTime) Source #

Specifies when the directory was created.

ddAlias :: Lens' DirectoryDescription (Maybe Text) Source #

The alias for the directory. If no alias has been created for the directory, the alias is the directory identifier, such as 'd-XXXXXXXXXX'.

ddName :: Lens' DirectoryDescription (Maybe Text) Source #

The fully-qualified name of the directory.

ddStageLastUpdatedDateTime :: Lens' DirectoryDescription (Maybe UTCTime) Source #

The date and time that the stage was last updated.

ddSSOEnabled :: Lens' DirectoryDescription (Maybe Bool) Source #

Indicates if single-sign on is enabled for the directory. For more information, see EnableSso and DisableSso.

ddDNSIPAddrs :: Lens' DirectoryDescription [Text] Source #

The IP addresses of the DNS servers for the directory. For a Simple AD or Microsoft AD directory, these are the IP addresses of the Simple AD or Microsoft AD directory servers. For an AD Connector directory, these are the IP addresses of the DNS servers or domain controllers in the on-premises directory to which the AD Connector is connected.

ddVPCSettings :: Lens' DirectoryDescription (Maybe DirectoryVPCSettingsDescription) Source #

A DirectoryVpcSettingsDescription object that contains additional information about a directory. This member is only present if the directory is a Simple AD or Managed AD directory.

ddStageReason :: Lens' DirectoryDescription (Maybe Text) Source #

Additional information about the directory stage.

ddConnectSettings :: Lens' DirectoryDescription (Maybe DirectoryConnectSettingsDescription) Source #

A DirectoryConnectSettingsDescription object that contains additional information about an AD Connector directory. This member is only present if the directory is an AD Connector directory.

ddDescription :: Lens' DirectoryDescription (Maybe Text) Source #

The textual description for the directory.

DirectoryLimits

data DirectoryLimits Source #

Contains directory limit information for a region.

See: directoryLimits smart constructor.

Instances

Eq DirectoryLimits Source # 
Data DirectoryLimits Source # 

Methods

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

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

toConstr :: DirectoryLimits -> Constr #

dataTypeOf :: DirectoryLimits -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DirectoryLimits Source # 
Show DirectoryLimits Source # 
Generic DirectoryLimits Source # 
FromJSON DirectoryLimits Source # 
Hashable DirectoryLimits Source # 
NFData DirectoryLimits Source # 

Methods

rnf :: DirectoryLimits -> () #

type Rep DirectoryLimits Source # 
type Rep DirectoryLimits = D1 (MetaData "DirectoryLimits" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "DirectoryLimits'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dlConnectedDirectoriesCurrentCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_dlCloudOnlyMicrosoftADLimitReached") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_dlConnectedDirectoriesLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_dlConnectedDirectoriesLimitReached") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dlCloudOnlyMicrosoftADLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_dlCloudOnlyDirectoriesLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)))) ((:*:) (S1 (MetaSel (Just Symbol "_dlCloudOnlyDirectoriesCurrentCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) ((:*:) (S1 (MetaSel (Just Symbol "_dlCloudOnlyDirectoriesLimitReached") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dlCloudOnlyMicrosoftADCurrentCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))))

dlConnectedDirectoriesCurrentCount :: Lens' DirectoryLimits (Maybe Natural) Source #

The current number of connected directories in the region.

dlCloudOnlyMicrosoftADLimitReached :: Lens' DirectoryLimits (Maybe Bool) Source #

Indicates if the Microsoft AD directory limit has been reached.

dlConnectedDirectoriesLimit :: Lens' DirectoryLimits (Maybe Natural) Source #

The maximum number of connected directories allowed in the region.

dlConnectedDirectoriesLimitReached :: Lens' DirectoryLimits (Maybe Bool) Source #

Indicates if the connected directory limit has been reached.

dlCloudOnlyMicrosoftADLimit :: Lens' DirectoryLimits (Maybe Natural) Source #

The maximum number of Microsoft AD directories allowed in the region.

dlCloudOnlyDirectoriesLimit :: Lens' DirectoryLimits (Maybe Natural) Source #

The maximum number of cloud directories allowed in the region.

dlCloudOnlyDirectoriesCurrentCount :: Lens' DirectoryLimits (Maybe Natural) Source #

The current number of cloud directories in the region.

dlCloudOnlyDirectoriesLimitReached :: Lens' DirectoryLimits (Maybe Bool) Source #

Indicates if the cloud directory limit has been reached.

dlCloudOnlyMicrosoftADCurrentCount :: Lens' DirectoryLimits (Maybe Natural) Source #

The current number of Microsoft AD directories in the region.

DirectoryVPCSettings

data DirectoryVPCSettings Source #

Contains VPC information for the CreateDirectory or CreateMicrosoftAD operation.

See: directoryVPCSettings smart constructor.

Instances

Eq DirectoryVPCSettings Source # 
Data DirectoryVPCSettings Source # 

Methods

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

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

toConstr :: DirectoryVPCSettings -> Constr #

dataTypeOf :: DirectoryVPCSettings -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DirectoryVPCSettings Source # 
Show DirectoryVPCSettings Source # 
Generic DirectoryVPCSettings Source # 
ToJSON DirectoryVPCSettings Source # 
Hashable DirectoryVPCSettings Source # 
NFData DirectoryVPCSettings Source # 

Methods

rnf :: DirectoryVPCSettings -> () #

type Rep DirectoryVPCSettings Source # 
type Rep DirectoryVPCSettings = D1 (MetaData "DirectoryVPCSettings" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "DirectoryVPCSettings'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dvsVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dvsSubnetIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))))

directoryVPCSettings Source #

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

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

dvsVPCId :: Lens' DirectoryVPCSettings Text Source #

The identifier of the VPC in which to create the directory.

dvsSubnetIds :: Lens' DirectoryVPCSettings [Text] Source #

The identifiers of the subnets for the directory servers. The two subnets must be in different Availability Zones. AWS Directory Service creates a directory server and a DNS server in each of these subnets.

DirectoryVPCSettingsDescription

data DirectoryVPCSettingsDescription Source #

Contains information about the directory.

See: directoryVPCSettingsDescription smart constructor.

Instances

Eq DirectoryVPCSettingsDescription Source # 
Data DirectoryVPCSettingsDescription Source # 

Methods

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

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

toConstr :: DirectoryVPCSettingsDescription -> Constr #

dataTypeOf :: DirectoryVPCSettingsDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DirectoryVPCSettingsDescription Source # 
Show DirectoryVPCSettingsDescription Source # 
Generic DirectoryVPCSettingsDescription Source # 
FromJSON DirectoryVPCSettingsDescription Source # 
Hashable DirectoryVPCSettingsDescription Source # 
NFData DirectoryVPCSettingsDescription Source # 
type Rep DirectoryVPCSettingsDescription Source # 
type Rep DirectoryVPCSettingsDescription = D1 (MetaData "DirectoryVPCSettingsDescription" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "DirectoryVPCSettingsDescription'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dvsdSubnetIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_dvsdVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_dvsdSecurityGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dvsdAvailabilityZones") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))

directoryVPCSettingsDescription :: DirectoryVPCSettingsDescription Source #

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

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

dvsdSubnetIds :: Lens' DirectoryVPCSettingsDescription [Text] Source #

The identifiers of the subnets for the directory servers.

dvsdVPCId :: Lens' DirectoryVPCSettingsDescription (Maybe Text) Source #

The identifier of the VPC that the directory is in.

dvsdSecurityGroupId :: Lens' DirectoryVPCSettingsDescription (Maybe Text) Source #

The security group identifier for the directory. If the directory was created before 8/1/2014, this is the identifier of the directory members security group that was created when the directory was created. If the directory was created after this date, this value is null.

dvsdAvailabilityZones :: Lens' DirectoryVPCSettingsDescription [Text] Source #

The list of Availability Zones that the directory is in.

EventTopic

data EventTopic Source #

Information about SNS topic and AWS Directory Service directory associations.

See: eventTopic smart constructor.

Instances

Eq EventTopic Source # 
Data EventTopic Source # 

Methods

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

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

toConstr :: EventTopic -> Constr #

dataTypeOf :: EventTopic -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EventTopic Source # 
Show EventTopic Source # 
Generic EventTopic Source # 

Associated Types

type Rep EventTopic :: * -> * #

FromJSON EventTopic Source # 
Hashable EventTopic Source # 
NFData EventTopic Source # 

Methods

rnf :: EventTopic -> () #

type Rep EventTopic Source # 
type Rep EventTopic = D1 (MetaData "EventTopic" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "EventTopic'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_etStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TopicStatus))) (S1 (MetaSel (Just Symbol "_etDirectoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_etTopicName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_etTopicARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_etCreatedDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))))))

eventTopic :: EventTopic Source #

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

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

etStatus :: Lens' EventTopic (Maybe TopicStatus) Source #

The topic registration status.

etDirectoryId :: Lens' EventTopic (Maybe Text) Source #

The Directory ID of an AWS Directory Service directory that will publish status messages to an SNS topic.

etTopicName :: Lens' EventTopic (Maybe Text) Source #

The name of an AWS SNS topic the receives status messages from the directory.

etTopicARN :: Lens' EventTopic (Maybe Text) Source #

The SNS topic ARN (Amazon Resource Name).

etCreatedDateTime :: Lens' EventTopic (Maybe UTCTime) Source #

The date and time of when you associated your directory with the SNS topic.

RadiusSettings

data RadiusSettings Source #

Contains information about a Remote Authentication Dial In User Service (RADIUS) server.

See: radiusSettings smart constructor.

Instances

Eq RadiusSettings Source # 
Data RadiusSettings Source # 

Methods

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

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

toConstr :: RadiusSettings -> Constr #

dataTypeOf :: RadiusSettings -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RadiusSettings Source # 
Show RadiusSettings Source # 
Generic RadiusSettings Source # 

Associated Types

type Rep RadiusSettings :: * -> * #

ToJSON RadiusSettings Source # 
FromJSON RadiusSettings Source # 
Hashable RadiusSettings Source # 
NFData RadiusSettings Source # 

Methods

rnf :: RadiusSettings -> () #

type Rep RadiusSettings Source # 

radiusSettings :: RadiusSettings Source #

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

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

rsRadiusRetries :: Lens' RadiusSettings (Maybe Natural) Source #

The maximum number of times that communication with the RADIUS server is attempted.

rsAuthenticationProtocol :: Lens' RadiusSettings (Maybe RadiusAuthenticationProtocol) Source #

The protocol specified for your RADIUS endpoints.

rsRadiusServers :: Lens' RadiusSettings [Text] Source #

An array of strings that contains the IP addresses of the RADIUS server endpoints, or the IP addresses of your RADIUS server load balancer.

rsSharedSecret :: Lens' RadiusSettings (Maybe Text) Source #

The shared secret code that was specified when your RADIUS endpoints were created.

rsRadiusTimeout :: Lens' RadiusSettings (Maybe Natural) Source #

The amount of time, in seconds, to wait for the RADIUS server to respond.

rsRadiusPort :: Lens' RadiusSettings (Maybe Natural) Source #

The port that your RADIUS server is using for communications. Your on-premises network must allow inbound traffic over this port from the AWS Directory Service servers.

Snapshot

data Snapshot Source #

Describes a directory snapshot.

See: snapshot smart constructor.

Instances

Eq Snapshot Source # 
Data Snapshot Source # 

Methods

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

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

toConstr :: Snapshot -> Constr #

dataTypeOf :: Snapshot -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Snapshot Source # 
Show Snapshot Source # 
Generic Snapshot Source # 

Associated Types

type Rep Snapshot :: * -> * #

Methods

from :: Snapshot -> Rep Snapshot x #

to :: Rep Snapshot x -> Snapshot #

FromJSON Snapshot Source # 
Hashable Snapshot Source # 

Methods

hashWithSalt :: Int -> Snapshot -> Int #

hash :: Snapshot -> Int #

NFData Snapshot Source # 

Methods

rnf :: Snapshot -> () #

type Rep Snapshot Source # 

snapshot :: Snapshot Source #

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

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

sStatus :: Lens' Snapshot (Maybe SnapshotStatus) Source #

The snapshot status.

sDirectoryId :: Lens' Snapshot (Maybe Text) Source #

The directory identifier.

sStartTime :: Lens' Snapshot (Maybe UTCTime) Source #

The date and time that the snapshot was taken.

sName :: Lens' Snapshot (Maybe Text) Source #

The descriptive name of the snapshot.

sType :: Lens' Snapshot (Maybe SnapshotType) Source #

The snapshot type.

sSnapshotId :: Lens' Snapshot (Maybe Text) Source #

The snapshot identifier.

SnapshotLimits

data SnapshotLimits Source #

Contains manual snapshot limit information for a directory.

See: snapshotLimits smart constructor.

Instances

Eq SnapshotLimits Source # 
Data SnapshotLimits Source # 

Methods

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

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

toConstr :: SnapshotLimits -> Constr #

dataTypeOf :: SnapshotLimits -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SnapshotLimits Source # 
Show SnapshotLimits Source # 
Generic SnapshotLimits Source # 

Associated Types

type Rep SnapshotLimits :: * -> * #

FromJSON SnapshotLimits Source # 
Hashable SnapshotLimits Source # 
NFData SnapshotLimits Source # 

Methods

rnf :: SnapshotLimits -> () #

type Rep SnapshotLimits Source # 
type Rep SnapshotLimits = D1 (MetaData "SnapshotLimits" "Network.AWS.DirectoryService.Types.Product" "amazonka-ds-1.4.3-CEZArOP1i373qyvcjwdjep" False) (C1 (MetaCons "SnapshotLimits'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_slManualSnapshotsLimitReached") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_slManualSnapshotsCurrentCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_slManualSnapshotsLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))

snapshotLimits :: SnapshotLimits Source #

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

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

slManualSnapshotsLimitReached :: Lens' SnapshotLimits (Maybe Bool) Source #

Indicates if the manual snapshot limit has been reached.

slManualSnapshotsCurrentCount :: Lens' SnapshotLimits (Maybe Natural) Source #

The current number of manual snapshots of the directory.

slManualSnapshotsLimit :: Lens' SnapshotLimits (Maybe Natural) Source #

The maximum number of manual snapshots allowed.

Trust

data Trust Source #

Describes a trust relationship between an Microsoft AD in the AWS cloud and an external domain.

See: trust smart constructor.

Instances

Eq Trust Source # 

Methods

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

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

Data Trust Source # 

Methods

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

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

toConstr :: Trust -> Constr #

dataTypeOf :: Trust -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Trust Source # 
Show Trust Source # 

Methods

showsPrec :: Int -> Trust -> ShowS #

show :: Trust -> String #

showList :: [Trust] -> ShowS #

Generic Trust Source # 

Associated Types

type Rep Trust :: * -> * #

Methods

from :: Trust -> Rep Trust x #

to :: Rep Trust x -> Trust #

FromJSON Trust Source # 
Hashable Trust Source # 

Methods

hashWithSalt :: Int -> Trust -> Int #

hash :: Trust -> Int #

NFData Trust Source # 

Methods

rnf :: Trust -> () #

type Rep Trust Source # 

trust :: Trust Source #

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

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

tDirectoryId :: Lens' Trust (Maybe Text) Source #

The Directory ID of the AWS directory involved in the trust relationship.

tTrustState :: Lens' Trust (Maybe TrustState) Source #

The trust relationship state.

tLastUpdatedDateTime :: Lens' Trust (Maybe UTCTime) Source #

The date and time that the trust relationship was last updated.

tTrustDirection :: Lens' Trust (Maybe TrustDirection) Source #

The trust relationship direction.

tStateLastUpdatedDateTime :: Lens' Trust (Maybe UTCTime) Source #

The date and time that the TrustState was last updated.

tTrustType :: Lens' Trust (Maybe TrustType) Source #

The trust relationship type.

tTrustStateReason :: Lens' Trust (Maybe Text) Source #

The reason for the TrustState.

tRemoteDomainName :: Lens' Trust (Maybe Text) Source #

The Fully Qualified Domain Name (FQDN) of the external domain involved in the trust relationship.

tTrustId :: Lens' Trust (Maybe Text) Source #

The unique ID of the trust relationship.

tCreatedDateTime :: Lens' Trust (Maybe UTCTime) Source #

The date and time that the trust relationship was created.