amazonka-cloud9-1.6.0: Amazon Cloud9 SDK.

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

Network.AWS.Cloud9.Types

Contents

Description

 

Synopsis

Service Configuration

cloud9 :: Service Source #

API version 2017-09-23 of the Amazon Cloud9 SDK configuration.

Errors

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

An access permissions issue occurred.

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

The target resource cannot be found.

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

Too many service requests were made over the given time period.

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

An internal server error occurred.

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

The target request is invalid.

EnvironmentStatus

data EnvironmentStatus Source #

Instances

Bounded EnvironmentStatus Source # 
Enum EnvironmentStatus Source # 
Eq EnvironmentStatus Source # 
Data EnvironmentStatus Source # 

Methods

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

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

toConstr :: EnvironmentStatus -> Constr #

dataTypeOf :: EnvironmentStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EnvironmentStatus -> () #

ToHeader EnvironmentStatus Source # 
ToQuery EnvironmentStatus Source # 
ToByteString EnvironmentStatus Source # 
FromText EnvironmentStatus Source # 
ToText EnvironmentStatus Source # 
type Rep EnvironmentStatus Source # 
type Rep EnvironmentStatus = D1 * (MetaData "EnvironmentStatus" "Network.AWS.Cloud9.Types.Sum" "amazonka-cloud9-1.6.0-7gsFvKEkpNuKHEnbgASzLW" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Connecting" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Creating" PrefixI False) (U1 *)) (C1 * (MetaCons "Deleting" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Error'" PrefixI False) (U1 *)) (C1 * (MetaCons "Ready" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Stopped" PrefixI False) (U1 *)) (C1 * (MetaCons "Stopping" PrefixI False) (U1 *)))))

EnvironmentType

data EnvironmentType Source #

Constructors

EC2 
SSH 

Instances

Bounded EnvironmentType Source # 
Enum EnvironmentType Source # 
Eq EnvironmentType Source # 
Data EnvironmentType Source # 

Methods

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

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

toConstr :: EnvironmentType -> Constr #

dataTypeOf :: EnvironmentType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EnvironmentType -> () #

ToHeader EnvironmentType Source # 
ToQuery EnvironmentType Source # 
ToByteString EnvironmentType Source # 
FromText EnvironmentType Source # 
ToText EnvironmentType Source # 
type Rep EnvironmentType Source # 
type Rep EnvironmentType = D1 * (MetaData "EnvironmentType" "Network.AWS.Cloud9.Types.Sum" "amazonka-cloud9-1.6.0-7gsFvKEkpNuKHEnbgASzLW" False) ((:+:) * (C1 * (MetaCons "EC2" PrefixI False) (U1 *)) (C1 * (MetaCons "SSH" PrefixI False) (U1 *)))

MemberPermissions

data MemberPermissions Source #

Constructors

MPReadOnly 
MPReadWrite 

Instances

Bounded MemberPermissions Source # 
Enum MemberPermissions Source # 
Eq MemberPermissions Source # 
Data MemberPermissions Source # 

Methods

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

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

toConstr :: MemberPermissions -> Constr #

dataTypeOf :: MemberPermissions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MemberPermissions Source # 
Read MemberPermissions Source # 
Show MemberPermissions Source # 
Generic MemberPermissions Source # 
Hashable MemberPermissions Source # 
ToJSON MemberPermissions Source # 
NFData MemberPermissions Source # 

Methods

rnf :: MemberPermissions -> () #

ToHeader MemberPermissions Source # 
ToQuery MemberPermissions Source # 
ToByteString MemberPermissions Source # 
FromText MemberPermissions Source # 
ToText MemberPermissions Source # 
type Rep MemberPermissions Source # 
type Rep MemberPermissions = D1 * (MetaData "MemberPermissions" "Network.AWS.Cloud9.Types.Sum" "amazonka-cloud9-1.6.0-7gsFvKEkpNuKHEnbgASzLW" False) ((:+:) * (C1 * (MetaCons "MPReadOnly" PrefixI False) (U1 *)) (C1 * (MetaCons "MPReadWrite" PrefixI False) (U1 *)))

Permissions

data Permissions Source #

Constructors

Owner 
ReadOnly 
ReadWrite 

Instances

Bounded Permissions Source # 
Enum Permissions Source # 
Eq Permissions Source # 
Data Permissions Source # 

Methods

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

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

toConstr :: Permissions -> Constr #

dataTypeOf :: Permissions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Permissions Source # 
Read Permissions Source # 
Show Permissions Source # 
Generic Permissions Source # 

Associated Types

type Rep Permissions :: * -> * #

Hashable Permissions Source # 
ToJSON Permissions Source # 
FromJSON Permissions Source # 
NFData Permissions Source # 

Methods

rnf :: Permissions -> () #

ToHeader Permissions Source # 
ToQuery Permissions Source # 
ToByteString Permissions Source # 
FromText Permissions Source # 
ToText Permissions Source # 

Methods

toText :: Permissions -> Text #

type Rep Permissions Source # 
type Rep Permissions = D1 * (MetaData "Permissions" "Network.AWS.Cloud9.Types.Sum" "amazonka-cloud9-1.6.0-7gsFvKEkpNuKHEnbgASzLW" False) ((:+:) * (C1 * (MetaCons "Owner" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ReadOnly" PrefixI False) (U1 *)) (C1 * (MetaCons "ReadWrite" PrefixI False) (U1 *))))

Environment

data Environment Source #

Information about an AWS Cloud9 development environment.

See: environment smart constructor.

Instances

Eq Environment Source # 
Data Environment Source # 

Methods

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

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

toConstr :: Environment -> Constr #

dataTypeOf :: Environment -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Environment Source # 
Show Environment Source # 
Generic Environment Source # 

Associated Types

type Rep Environment :: * -> * #

Hashable Environment Source # 
FromJSON Environment Source # 
NFData Environment Source # 

Methods

rnf :: Environment -> () #

type Rep Environment Source # 

environment :: Environment Source #

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

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

  • eArn - The Amazon Resource Name (ARN) of the environment.
  • eOwnerARN - The Amazon Resource Name (ARN) of the environment owner.
  • eName - The name of the environment.
  • eId - The ID of the environment.
  • eType - The type of environment. Valid values include the following: * ec2 : An Amazon Elastic Compute Cloud (Amazon EC2) instance connects to the environment. * ssh : Your own server connects to the environment.
  • eDescription - The description for the environment.

eArn :: Lens' Environment (Maybe Text) Source #

The Amazon Resource Name (ARN) of the environment.

eOwnerARN :: Lens' Environment (Maybe Text) Source #

The Amazon Resource Name (ARN) of the environment owner.

eName :: Lens' Environment (Maybe Text) Source #

The name of the environment.

eId :: Lens' Environment (Maybe Text) Source #

The ID of the environment.

eType :: Lens' Environment (Maybe EnvironmentType) Source #

The type of environment. Valid values include the following: * ec2 : An Amazon Elastic Compute Cloud (Amazon EC2) instance connects to the environment. * ssh : Your own server connects to the environment.

eDescription :: Lens' Environment (Maybe Text) Source #

The description for the environment.

EnvironmentMember

data EnvironmentMember Source #

Information about an environment member for an AWS Cloud9 development environment.

See: environmentMember smart constructor.

Instances

Eq EnvironmentMember Source # 
Data EnvironmentMember Source # 

Methods

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

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

toConstr :: EnvironmentMember -> Constr #

dataTypeOf :: EnvironmentMember -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EnvironmentMember -> () #

type Rep EnvironmentMember Source # 
type Rep EnvironmentMember = D1 * (MetaData "EnvironmentMember" "Network.AWS.Cloud9.Types.Product" "amazonka-cloud9-1.6.0-7gsFvKEkpNuKHEnbgASzLW" False) (C1 * (MetaCons "EnvironmentMember'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_emLastAccess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_emUserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_emUserARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_emPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Permissions))) (S1 * (MetaSel (Just Symbol "_emEnvironmentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

environmentMember :: EnvironmentMember Source #

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

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

  • emLastAccess - The time, expressed in epoch time format, when the environment member last opened the environment.
  • emUserId - The user ID in AWS Identity and Access Management (AWS IAM) of the environment member.
  • emUserARN - The Amazon Resource Name (ARN) of the environment member.
  • emPermissions - The type of environment member permissions associated with this environment member. Available values include: * owner : Owns the environment. * read-only : Has read-only access to the environment. * read-write : Has read-write access to the environment.
  • emEnvironmentId - The ID of the environment for the environment member.

emLastAccess :: Lens' EnvironmentMember (Maybe UTCTime) Source #

The time, expressed in epoch time format, when the environment member last opened the environment.

emUserId :: Lens' EnvironmentMember (Maybe Text) Source #

The user ID in AWS Identity and Access Management (AWS IAM) of the environment member.

emUserARN :: Lens' EnvironmentMember (Maybe Text) Source #

The Amazon Resource Name (ARN) of the environment member.

emPermissions :: Lens' EnvironmentMember (Maybe Permissions) Source #

The type of environment member permissions associated with this environment member. Available values include: * owner : Owns the environment. * read-only : Has read-only access to the environment. * read-write : Has read-write access to the environment.

emEnvironmentId :: Lens' EnvironmentMember (Maybe Text) Source #

The ID of the environment for the environment member.