amazonka-workspaces-1.4.2: Amazon WorkSpaces 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.WorkSpaces

Contents

Description

Amazon WorkSpaces Service

This is the Amazon WorkSpaces API Reference. This guide provides detailed information about Amazon WorkSpaces operations, data types, parameters, and errors.

Synopsis

Service Configuration

workSpaces :: Service Source #

API version '2015-04-08' of the Amazon WorkSpaces 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 WorkSpaces.

ResourceUnavailableException

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

The specified resource is not available.

InvalidParameterValuesException

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

One or more parameter values are not valid.

ResourceLimitExceededException

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

Your resource limits have been exceeded.

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.

DescribeWorkspaceDirectories

DescribeWorkspaceBundles

RebuildWorkspaces

RebootWorkspaces

TerminateWorkspaces

CreateWorkspaces

DescribeWorkspaces

Types

Compute

data Compute Source #

Constructors

Performance 
Standard 
Value 

Instances

Bounded Compute Source # 
Enum Compute Source # 
Eq Compute Source # 

Methods

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

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

Data Compute Source # 

Methods

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

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

toConstr :: Compute -> Constr #

dataTypeOf :: Compute -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Compute Source # 
Read Compute Source # 
Show Compute Source # 
Generic Compute Source # 

Associated Types

type Rep Compute :: * -> * #

Methods

from :: Compute -> Rep Compute x #

to :: Rep Compute x -> Compute #

FromJSON Compute Source # 
Hashable Compute Source # 

Methods

hashWithSalt :: Int -> Compute -> Int #

hash :: Compute -> Int #

NFData Compute Source # 

Methods

rnf :: Compute -> () #

ToHeader Compute Source # 

Methods

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

ToQuery Compute Source # 
ToByteString Compute Source # 

Methods

toBS :: Compute -> ByteString #

FromText Compute Source # 
ToText Compute Source # 

Methods

toText :: Compute -> Text #

type Rep Compute Source # 
type Rep Compute = D1 (MetaData "Compute" "Network.AWS.WorkSpaces.Types.Sum" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) ((:+:) (C1 (MetaCons "Performance" PrefixI False) U1) ((:+:) (C1 (MetaCons "Standard" PrefixI False) U1) (C1 (MetaCons "Value" PrefixI False) U1)))

WorkspaceDirectoryState

data WorkspaceDirectoryState Source #

Instances

Bounded WorkspaceDirectoryState Source # 
Enum WorkspaceDirectoryState Source # 
Eq WorkspaceDirectoryState Source # 
Data WorkspaceDirectoryState Source # 

Methods

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

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

toConstr :: WorkspaceDirectoryState -> Constr #

dataTypeOf :: WorkspaceDirectoryState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: WorkspaceDirectoryState -> () #

ToHeader WorkspaceDirectoryState Source # 
ToQuery WorkspaceDirectoryState Source # 
ToByteString WorkspaceDirectoryState Source # 
FromText WorkspaceDirectoryState Source # 
ToText WorkspaceDirectoryState Source # 
type Rep WorkspaceDirectoryState Source # 
type Rep WorkspaceDirectoryState = D1 (MetaData "WorkspaceDirectoryState" "Network.AWS.WorkSpaces.Types.Sum" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) ((:+:) ((:+:) (C1 (MetaCons "Deregistered" PrefixI False) U1) (C1 (MetaCons "Deregistering" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Error'" PrefixI False) U1) ((:+:) (C1 (MetaCons "Registered" PrefixI False) U1) (C1 (MetaCons "Registering" PrefixI False) U1))))

WorkspaceDirectoryType

data WorkspaceDirectoryType Source #

Constructors

AdConnector 
SimpleAd 

Instances

Bounded WorkspaceDirectoryType Source # 
Enum WorkspaceDirectoryType Source # 
Eq WorkspaceDirectoryType Source # 
Data WorkspaceDirectoryType Source # 

Methods

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

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

toConstr :: WorkspaceDirectoryType -> Constr #

dataTypeOf :: WorkspaceDirectoryType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: WorkspaceDirectoryType -> () #

ToHeader WorkspaceDirectoryType Source # 
ToQuery WorkspaceDirectoryType Source # 
ToByteString WorkspaceDirectoryType Source # 
FromText WorkspaceDirectoryType Source # 
ToText WorkspaceDirectoryType Source # 
type Rep WorkspaceDirectoryType Source # 
type Rep WorkspaceDirectoryType = D1 (MetaData "WorkspaceDirectoryType" "Network.AWS.WorkSpaces.Types.Sum" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) ((:+:) (C1 (MetaCons "AdConnector" PrefixI False) U1) (C1 (MetaCons "SimpleAd" PrefixI False) U1))

WorkspaceState

data WorkspaceState Source #

Instances

Bounded WorkspaceState Source # 
Enum WorkspaceState Source # 
Eq WorkspaceState Source # 
Data WorkspaceState Source # 

Methods

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

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

toConstr :: WorkspaceState -> Constr #

dataTypeOf :: WorkspaceState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WorkspaceState Source # 
Read WorkspaceState Source # 
Show WorkspaceState Source # 
Generic WorkspaceState Source # 

Associated Types

type Rep WorkspaceState :: * -> * #

FromJSON WorkspaceState Source # 
Hashable WorkspaceState Source # 
NFData WorkspaceState Source # 

Methods

rnf :: WorkspaceState -> () #

ToHeader WorkspaceState Source # 
ToQuery WorkspaceState Source # 
ToByteString WorkspaceState Source # 
FromText WorkspaceState Source # 
ToText WorkspaceState Source # 
type Rep WorkspaceState Source # 
type Rep WorkspaceState = D1 (MetaData "WorkspaceState" "Network.AWS.WorkSpaces.Types.Sum" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "WSAvailable" PrefixI False) U1) (C1 (MetaCons "WSError'" PrefixI False) U1)) ((:+:) (C1 (MetaCons "WSImpaired" PrefixI False) U1) ((:+:) (C1 (MetaCons "WSPending" PrefixI False) U1) (C1 (MetaCons "WSRebooting" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "WSRebuilding" PrefixI False) U1) (C1 (MetaCons "WSSuspended" PrefixI False) U1)) ((:+:) (C1 (MetaCons "WSTerminated" PrefixI False) U1) ((:+:) (C1 (MetaCons "WSTerminating" PrefixI False) U1) (C1 (MetaCons "WSUnhealthy" PrefixI False) U1)))))

ComputeType

data ComputeType Source #

Contains information about the compute type of a WorkSpace bundle.

See: computeType smart constructor.

Instances

Eq ComputeType Source # 
Data ComputeType Source # 

Methods

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

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

toConstr :: ComputeType -> Constr #

dataTypeOf :: ComputeType -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ComputeType Source # 
Show ComputeType Source # 
Generic ComputeType Source # 

Associated Types

type Rep ComputeType :: * -> * #

FromJSON ComputeType Source # 
Hashable ComputeType Source # 
NFData ComputeType Source # 

Methods

rnf :: ComputeType -> () #

type Rep ComputeType Source # 
type Rep ComputeType = D1 (MetaData "ComputeType" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" True) (C1 (MetaCons "ComputeType'" PrefixI True) (S1 (MetaSel (Just Symbol "_ctName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Compute))))

computeType :: ComputeType Source #

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

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

ctName :: Lens' ComputeType (Maybe Compute) Source #

The name of the compute type for the bundle.

DefaultWorkspaceCreationProperties

data DefaultWorkspaceCreationProperties Source #

Contains default WorkSpace creation information.

See: defaultWorkspaceCreationProperties smart constructor.

Instances

Eq DefaultWorkspaceCreationProperties Source # 
Data DefaultWorkspaceCreationProperties Source # 

Methods

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

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

toConstr :: DefaultWorkspaceCreationProperties -> Constr #

dataTypeOf :: DefaultWorkspaceCreationProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DefaultWorkspaceCreationProperties Source # 
Show DefaultWorkspaceCreationProperties Source # 
Generic DefaultWorkspaceCreationProperties Source # 
FromJSON DefaultWorkspaceCreationProperties Source # 
Hashable DefaultWorkspaceCreationProperties Source # 
NFData DefaultWorkspaceCreationProperties Source # 
type Rep DefaultWorkspaceCreationProperties Source # 
type Rep DefaultWorkspaceCreationProperties = D1 (MetaData "DefaultWorkspaceCreationProperties" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) (C1 (MetaCons "DefaultWorkspaceCreationProperties'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dwcpCustomSecurityGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dwcpUserEnabledAsLocalAdministrator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_dwcpEnableWorkDocs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_dwcpEnableInternetAccess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dwcpDefaultOu") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

dwcpCustomSecurityGroupId :: Lens' DefaultWorkspaceCreationProperties (Maybe Text) Source #

The identifier of any custom security groups that are applied to the WorkSpaces when they are created.

dwcpUserEnabledAsLocalAdministrator :: Lens' DefaultWorkspaceCreationProperties (Maybe Bool) Source #

The WorkSpace user is an administrator on the WorkSpace.

dwcpEnableWorkDocs :: Lens' DefaultWorkspaceCreationProperties (Maybe Bool) Source #

Specifies if the directory is enabled for Amazon WorkDocs.

dwcpEnableInternetAccess :: Lens' DefaultWorkspaceCreationProperties (Maybe Bool) Source #

A public IP address will be attached to all WorkSpaces that are created or rebuilt.

dwcpDefaultOu :: Lens' DefaultWorkspaceCreationProperties (Maybe Text) Source #

The organizational unit (OU) in the directory that the WorkSpace machine accounts are placed in.

FailedCreateWorkspaceRequest

data FailedCreateWorkspaceRequest Source #

Contains information about a WorkSpace that could not be created.

See: failedCreateWorkspaceRequest smart constructor.

Instances

Eq FailedCreateWorkspaceRequest Source # 
Data FailedCreateWorkspaceRequest Source # 

Methods

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

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

toConstr :: FailedCreateWorkspaceRequest -> Constr #

dataTypeOf :: FailedCreateWorkspaceRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FailedCreateWorkspaceRequest Source # 
Show FailedCreateWorkspaceRequest Source # 
Generic FailedCreateWorkspaceRequest Source # 
FromJSON FailedCreateWorkspaceRequest Source # 
Hashable FailedCreateWorkspaceRequest Source # 
NFData FailedCreateWorkspaceRequest Source # 
type Rep FailedCreateWorkspaceRequest Source # 
type Rep FailedCreateWorkspaceRequest = D1 (MetaData "FailedCreateWorkspaceRequest" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) (C1 (MetaCons "FailedCreateWorkspaceRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fcwrWorkspaceRequest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WorkspaceRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_fcwrErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fcwrErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

failedCreateWorkspaceRequest :: FailedCreateWorkspaceRequest Source #

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

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

fcwrWorkspaceRequest :: Lens' FailedCreateWorkspaceRequest (Maybe WorkspaceRequest) Source #

A WorkspaceRequest object that contains the information about the WorkSpace that could not be created.

FailedWorkspaceChangeRequest

data FailedWorkspaceChangeRequest Source #

Contains information about a WorkSpace that could not be rebooted (RebootWorkspaces), rebuilt (RebuildWorkspaces), or terminated (TerminateWorkspaces).

See: failedWorkspaceChangeRequest smart constructor.

Instances

Eq FailedWorkspaceChangeRequest Source # 
Data FailedWorkspaceChangeRequest Source # 

Methods

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

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

toConstr :: FailedWorkspaceChangeRequest -> Constr #

dataTypeOf :: FailedWorkspaceChangeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FailedWorkspaceChangeRequest Source # 
Show FailedWorkspaceChangeRequest Source # 
Generic FailedWorkspaceChangeRequest Source # 
FromJSON FailedWorkspaceChangeRequest Source # 
Hashable FailedWorkspaceChangeRequest Source # 
NFData FailedWorkspaceChangeRequest Source # 
type Rep FailedWorkspaceChangeRequest Source # 
type Rep FailedWorkspaceChangeRequest = D1 (MetaData "FailedWorkspaceChangeRequest" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) (C1 (MetaCons "FailedWorkspaceChangeRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fwcrErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_fwcrWorkspaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fwcrErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

failedWorkspaceChangeRequest :: FailedWorkspaceChangeRequest Source #

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

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

fwcrWorkspaceId :: Lens' FailedWorkspaceChangeRequest (Maybe Text) Source #

The identifier of the WorkSpace.

RebootRequest

data RebootRequest Source #

Contains information used with the RebootWorkspaces operation to reboot a WorkSpace.

See: rebootRequest smart constructor.

Instances

Eq RebootRequest Source # 
Data RebootRequest Source # 

Methods

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

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

toConstr :: RebootRequest -> Constr #

dataTypeOf :: RebootRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RebootRequest Source # 
Show RebootRequest Source # 
Generic RebootRequest Source # 

Associated Types

type Rep RebootRequest :: * -> * #

ToJSON RebootRequest Source # 
Hashable RebootRequest Source # 
NFData RebootRequest Source # 

Methods

rnf :: RebootRequest -> () #

type Rep RebootRequest Source # 
type Rep RebootRequest = D1 (MetaData "RebootRequest" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" True) (C1 (MetaCons "RebootRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_rWorkspaceId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

rebootRequest Source #

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

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

rWorkspaceId :: Lens' RebootRequest Text Source #

The identifier of the WorkSpace to reboot.

RebuildRequest

data RebuildRequest Source #

Contains information used with the RebuildWorkspaces operation to rebuild a WorkSpace.

See: rebuildRequest smart constructor.

Instances

Eq RebuildRequest Source # 
Data RebuildRequest Source # 

Methods

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

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

toConstr :: RebuildRequest -> Constr #

dataTypeOf :: RebuildRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RebuildRequest Source # 
Show RebuildRequest Source # 
Generic RebuildRequest Source # 

Associated Types

type Rep RebuildRequest :: * -> * #

ToJSON RebuildRequest Source # 
Hashable RebuildRequest Source # 
NFData RebuildRequest Source # 

Methods

rnf :: RebuildRequest -> () #

type Rep RebuildRequest Source # 
type Rep RebuildRequest = D1 (MetaData "RebuildRequest" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" True) (C1 (MetaCons "RebuildRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_rrWorkspaceId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

rebuildRequest Source #

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

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

rrWorkspaceId :: Lens' RebuildRequest Text Source #

The identifier of the WorkSpace to rebuild.

TerminateRequest

data TerminateRequest Source #

Contains information used with the TerminateWorkspaces operation to terminate a WorkSpace.

See: terminateRequest smart constructor.

Instances

Eq TerminateRequest Source # 
Data TerminateRequest Source # 

Methods

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

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

toConstr :: TerminateRequest -> Constr #

dataTypeOf :: TerminateRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: TerminateRequest -> () #

type Rep TerminateRequest Source # 
type Rep TerminateRequest = D1 (MetaData "TerminateRequest" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" True) (C1 (MetaCons "TerminateRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_trWorkspaceId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

terminateRequest Source #

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

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

trWorkspaceId :: Lens' TerminateRequest Text Source #

The identifier of the WorkSpace to terminate.

UserStorage

data UserStorage Source #

Contains information about the user storage for a WorkSpace bundle.

See: userStorage smart constructor.

Instances

Eq UserStorage Source # 
Data UserStorage Source # 

Methods

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

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

toConstr :: UserStorage -> Constr #

dataTypeOf :: UserStorage -> DataType #

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

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

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

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

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

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

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

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

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

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

Read UserStorage Source # 
Show UserStorage Source # 
Generic UserStorage Source # 

Associated Types

type Rep UserStorage :: * -> * #

FromJSON UserStorage Source # 
Hashable UserStorage Source # 
NFData UserStorage Source # 

Methods

rnf :: UserStorage -> () #

type Rep UserStorage Source # 
type Rep UserStorage = D1 (MetaData "UserStorage" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" True) (C1 (MetaCons "UserStorage'" PrefixI True) (S1 (MetaSel (Just Symbol "_usCapacity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

userStorage :: UserStorage Source #

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

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

usCapacity :: Lens' UserStorage (Maybe Text) Source #

The amount of user storage for the bundle.

Workspace

data Workspace Source #

Contains information about a WorkSpace.

See: workspace smart constructor.

Instances

Eq Workspace Source # 
Data Workspace Source # 

Methods

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

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

toConstr :: Workspace -> Constr #

dataTypeOf :: Workspace -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Workspace Source # 
Show Workspace Source # 
Generic Workspace Source # 

Associated Types

type Rep Workspace :: * -> * #

FromJSON Workspace Source # 
Hashable Workspace Source # 
NFData Workspace Source # 

Methods

rnf :: Workspace -> () #

type Rep Workspace Source # 
type Rep Workspace = D1 (MetaData "Workspace" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) (C1 (MetaCons "Workspace'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wDirectoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_wState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WorkspaceState))) (S1 (MetaSel (Just Symbol "_wIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_wUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_wSubnetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wRootVolumeEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_wErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wVolumeEncryptionKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wComputerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wWorkspaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_wUserVolumeEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_wErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

workspace :: Workspace Source #

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

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

wDirectoryId :: Lens' Workspace (Maybe Text) Source #

The identifier of the AWS Directory Service directory that the WorkSpace belongs to.

wState :: Lens' Workspace (Maybe WorkspaceState) Source #

The operational state of the WorkSpace.

wIPAddress :: Lens' Workspace (Maybe Text) Source #

The IP address of the WorkSpace.

wUserName :: Lens' Workspace (Maybe Text) Source #

The user that the WorkSpace is assigned to.

wSubnetId :: Lens' Workspace (Maybe Text) Source #

The identifier of the subnet that the WorkSpace is in.

wBundleId :: Lens' Workspace (Maybe Text) Source #

The identifier of the bundle that the WorkSpace was created from.

wRootVolumeEncryptionEnabled :: Lens' Workspace (Maybe Bool) Source #

Specifies whether the data stored on the root volume, or C: drive, is encrypted.

wErrorCode :: Lens' Workspace (Maybe Text) Source #

If the WorkSpace could not be created, this contains the error code.

wVolumeEncryptionKey :: Lens' Workspace (Maybe Text) Source #

The KMS key used to encrypt data stored on your WorkSpace.

wComputerName :: Lens' Workspace (Maybe Text) Source #

The name of the WorkSpace as seen by the operating system.

wWorkspaceId :: Lens' Workspace (Maybe Text) Source #

The identifier of the WorkSpace.

wUserVolumeEncryptionEnabled :: Lens' Workspace (Maybe Bool) Source #

Specifies whether the data stored on the user volume, or D: drive, is encrypted.

wErrorMessage :: Lens' Workspace (Maybe Text) Source #

If the WorkSpace could not be created, this contains a textual error message that describes the failure.

WorkspaceBundle

data WorkspaceBundle Source #

Contains information about a WorkSpace bundle.

See: workspaceBundle smart constructor.

Instances

Eq WorkspaceBundle Source # 
Data WorkspaceBundle Source # 

Methods

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

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

toConstr :: WorkspaceBundle -> Constr #

dataTypeOf :: WorkspaceBundle -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: WorkspaceBundle -> () #

type Rep WorkspaceBundle Source # 

workspaceBundle :: WorkspaceBundle Source #

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

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

wbBundleId :: Lens' WorkspaceBundle (Maybe Text) Source #

The bundle identifier.

wbOwner :: Lens' WorkspaceBundle (Maybe Text) Source #

The owner of the bundle. This contains the owner's account identifier, or AMAZON if the bundle is provided by AWS.

wbName :: Lens' WorkspaceBundle (Maybe Text) Source #

The name of the bundle.

wbComputeType :: Lens' WorkspaceBundle (Maybe ComputeType) Source #

A ComputeType object that specifies the compute type for the bundle.

wbUserStorage :: Lens' WorkspaceBundle (Maybe UserStorage) Source #

A UserStorage object that specifies the amount of user storage that the bundle contains.

wbDescription :: Lens' WorkspaceBundle (Maybe Text) Source #

The bundle description.

WorkspaceDirectory

data WorkspaceDirectory Source #

Contains information about an AWS Directory Service directory for use with Amazon WorkSpaces.

See: workspaceDirectory smart constructor.

Instances

Eq WorkspaceDirectory Source # 
Data WorkspaceDirectory Source # 

Methods

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

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

toConstr :: WorkspaceDirectory -> Constr #

dataTypeOf :: WorkspaceDirectory -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: WorkspaceDirectory -> () #

type Rep WorkspaceDirectory Source # 
type Rep WorkspaceDirectory = D1 (MetaData "WorkspaceDirectory" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) (C1 (MetaCons "WorkspaceDirectory'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wdRegistrationCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_wdIAMRoleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wdDirectoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_wdState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WorkspaceDirectoryState))) ((:*:) (S1 (MetaSel (Just Symbol "_wdCustomerUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wdSubnetIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wdAlias") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_wdWorkspaceSecurityGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wdDirectoryType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WorkspaceDirectoryType))))) ((:*:) (S1 (MetaSel (Just Symbol "_wdWorkspaceCreationProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DefaultWorkspaceCreationProperties))) ((:*:) (S1 (MetaSel (Just Symbol "_wdDNSIPAddresses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_wdDirectoryName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

wdRegistrationCode :: Lens' WorkspaceDirectory (Maybe Text) Source #

The registration code for the directory. This is the code that users enter in their Amazon WorkSpaces client application to connect to the directory.

wdIAMRoleId :: Lens' WorkspaceDirectory (Maybe Text) Source #

The identifier of the IAM role. This is the role that allows Amazon WorkSpaces to make calls to other services, such as Amazon EC2, on your behalf.

wdDirectoryId :: Lens' WorkspaceDirectory (Maybe Text) Source #

The directory identifier.

wdState :: Lens' WorkspaceDirectory (Maybe WorkspaceDirectoryState) Source #

The state of the directory's registration with Amazon WorkSpaces

wdCustomerUserName :: Lens' WorkspaceDirectory (Maybe Text) Source #

The user name for the service account.

wdSubnetIds :: Lens' WorkspaceDirectory [Text] Source #

An array of strings that contains the identifiers of the subnets used with the directory.

wdAlias :: Lens' WorkspaceDirectory (Maybe Text) Source #

The directory alias.

wdWorkspaceSecurityGroupId :: Lens' WorkspaceDirectory (Maybe Text) Source #

The identifier of the security group that is assigned to new WorkSpaces.

wdWorkspaceCreationProperties :: Lens' WorkspaceDirectory (Maybe DefaultWorkspaceCreationProperties) Source #

A structure that specifies the default creation properties for all WorkSpaces in the directory.

wdDNSIPAddresses :: Lens' WorkspaceDirectory [Text] Source #

An array of strings that contains the IP addresses of the DNS servers for the directory.

wdDirectoryName :: Lens' WorkspaceDirectory (Maybe Text) Source #

The name of the directory.

WorkspaceRequest

data WorkspaceRequest Source #

Contains information about a WorkSpace creation request.

See: workspaceRequest smart constructor.

Instances

Eq WorkspaceRequest Source # 
Data WorkspaceRequest Source # 

Methods

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

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

toConstr :: WorkspaceRequest -> Constr #

dataTypeOf :: WorkspaceRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WorkspaceRequest Source # 
Show WorkspaceRequest Source # 
Generic WorkspaceRequest Source # 
ToJSON WorkspaceRequest Source # 
FromJSON WorkspaceRequest Source # 
Hashable WorkspaceRequest Source # 
NFData WorkspaceRequest Source # 

Methods

rnf :: WorkspaceRequest -> () #

type Rep WorkspaceRequest Source # 
type Rep WorkspaceRequest = D1 (MetaData "WorkspaceRequest" "Network.AWS.WorkSpaces.Types.Product" "amazonka-workspaces-1.4.2-E1tn9WBBgtH4LpyYrCvgju" False) (C1 (MetaCons "WorkspaceRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wrRootVolumeEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_wrVolumeEncryptionKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wrUserVolumeEncryptionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_wrDirectoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_wrUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_wrBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))))

workspaceRequest Source #

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

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

wrRootVolumeEncryptionEnabled :: Lens' WorkspaceRequest (Maybe Bool) Source #

Specifies whether the data stored on the root volume, or C: drive, is encrypted.

wrVolumeEncryptionKey :: Lens' WorkspaceRequest (Maybe Text) Source #

The KMS key used to encrypt data stored on your WorkSpace.

wrUserVolumeEncryptionEnabled :: Lens' WorkspaceRequest (Maybe Bool) Source #

Specifies whether the data stored on the user volume, or D: drive, is encrypted.

wrDirectoryId :: Lens' WorkspaceRequest Text Source #

The identifier of the AWS Directory Service directory to create the WorkSpace in. You can use the DescribeWorkspaceDirectories operation to obtain a list of the directories that are available.

wrUserName :: Lens' WorkspaceRequest Text Source #

The username that the WorkSpace is assigned to. This username must exist in the AWS Directory Service directory specified by the DirectoryId member.

wrBundleId :: Lens' WorkspaceRequest Text Source #

The identifier of the bundle to create the WorkSpace from. You can use the DescribeWorkspaceBundles operation to obtain a list of the bundles that are available.