amazonka-lightsail-1.6.0: Amazon Lightsail 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.Lightsail

Contents

Description

Amazon Lightsail is the easiest way to get started with AWS for developers who just need virtual private servers. Lightsail includes everything you need to launch your project quickly - a virtual machine, SSD-based storage, data transfer, DNS management, and a static IP - for a low, predictable price. You manage those Lightsail servers through the Lightsail console or by using the API or command-line interface (CLI).

For more information about Lightsail concepts and tasks, see the Lightsail Dev Guide .

To use the Lightsail API or the CLI, you will need to use AWS Identity and Access Management (IAM) to generate access keys. For details about how to set this up, see the Lightsail Dev Guide .

Synopsis

Service Configuration

lightsail :: Service Source #

API version 2016-11-28 of the Amazon Lightsail 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 Lightsail.

AccessDeniedException

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

Lightsail throws this exception when the user cannot be authenticated or uses invalid credentials to access a resource.

AccountSetupInProgressException

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

Lightsail throws this exception when an account is still in the setup in progress state.

NotFoundException

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

Lightsail throws this exception when it cannot find a resource.

OperationFailureException

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

Lightsail throws this exception when an operation fails to execute.

ServiceException

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

A general service exception.

UnauthenticatedException

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

Lightsail throws this exception when the user has not been authenticated.

InvalidInputException

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

Lightsail throws this exception when user input does not conform to the validation rules of an input field.

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.

CloseInstancePublicPorts

AllocateStaticIP

DeleteKeyPair

DeleteInstanceSnapshot

GetInstances (Paginated)

GetLoadBalancer

GetInstance

AttachStaticIP

DetachDisk

DownloadDefaultKeyPair

DeleteLoadBalancerTLSCertificate

GetDomains (Paginated)

CreateLoadBalancerTLSCertificate

CreateDomainEntry

ImportKeyPair

GetInstanceSnapshots (Paginated)

ReleaseStaticIP

DeleteInstance

RebootInstance

DeleteLoadBalancer

CreateDiskFromSnapshot

GetInstanceSnapshot

GetDomain

GetActiveNames (Paginated)

GetInstanceAccessDetails

StopInstance

DetachInstancesFromLoadBalancer

CreateInstanceSnapshot

IsVPCPeered

GetStaticIPs (Paginated)

UnpeerVPC

DeleteDisk

CreateInstancesFromSnapshot

CreateDomain

GetDiskSnapshots

PeerVPC

GetLoadBalancers

AttachLoadBalancerTLSCertificate

UpdateLoadBalancerAttribute

GetDiskSnapshot

GetStaticIP

GetBlueprints (Paginated)

GetInstancePortStates

CreateDiskSnapshot

DeleteDomainEntry

UpdateDomainEntry

GetRegions

DeleteDiskSnapshot

GetLoadBalancerMetricData

GetInstanceState

GetKeyPairs (Paginated)

GetOperations (Paginated)

GetDisks

AttachInstancesToLoadBalancer

GetOperation

GetInstanceMetricData

GetKeyPair

PutInstancePublicPorts

GetDisk

CreateLoadBalancer

AttachDisk

DetachStaticIP

CreateInstances

OpenInstancePublicPorts

GetBundles (Paginated)

DeleteDomain

GetLoadBalancerTLSCertificates

CreateDisk

GetOperationsForResource

CreateKeyPair

StartInstance

Types

AccessDirection

data AccessDirection Source #

Constructors

Inbound 
Outbound 

Instances

Bounded AccessDirection Source # 
Enum AccessDirection Source # 
Eq AccessDirection Source # 
Data AccessDirection Source # 

Methods

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

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

toConstr :: AccessDirection -> Constr #

dataTypeOf :: AccessDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: AccessDirection -> () #

ToHeader AccessDirection Source # 
ToQuery AccessDirection Source # 
ToByteString AccessDirection Source # 
FromText AccessDirection Source # 
ToText AccessDirection Source # 
type Rep AccessDirection Source # 
type Rep AccessDirection = D1 * (MetaData "AccessDirection" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "Inbound" PrefixI False) (U1 *)) (C1 * (MetaCons "Outbound" PrefixI False) (U1 *)))

BlueprintType

data BlueprintType Source #

Constructors

App 
OS 

Instances

Bounded BlueprintType Source # 
Enum BlueprintType Source # 
Eq BlueprintType Source # 
Data BlueprintType Source # 

Methods

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

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

toConstr :: BlueprintType -> Constr #

dataTypeOf :: BlueprintType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BlueprintType Source # 
Read BlueprintType Source # 
Show BlueprintType Source # 
Generic BlueprintType Source # 

Associated Types

type Rep BlueprintType :: * -> * #

Hashable BlueprintType Source # 
FromJSON BlueprintType Source # 
NFData BlueprintType Source # 

Methods

rnf :: BlueprintType -> () #

ToHeader BlueprintType Source # 
ToQuery BlueprintType Source # 
ToByteString BlueprintType Source # 
FromText BlueprintType Source # 
ToText BlueprintType Source # 

Methods

toText :: BlueprintType -> Text #

type Rep BlueprintType Source # 
type Rep BlueprintType = D1 * (MetaData "BlueprintType" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "App" PrefixI False) (U1 *)) (C1 * (MetaCons "OS" PrefixI False) (U1 *)))

DiskSnapshotState

data DiskSnapshotState Source #

Instances

Bounded DiskSnapshotState Source # 
Enum DiskSnapshotState Source # 
Eq DiskSnapshotState Source # 
Data DiskSnapshotState Source # 

Methods

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

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

toConstr :: DiskSnapshotState -> Constr #

dataTypeOf :: DiskSnapshotState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: DiskSnapshotState -> () #

ToHeader DiskSnapshotState Source # 
ToQuery DiskSnapshotState Source # 
ToByteString DiskSnapshotState Source # 
FromText DiskSnapshotState Source # 
ToText DiskSnapshotState Source # 
type Rep DiskSnapshotState Source # 
type Rep DiskSnapshotState = D1 * (MetaData "DiskSnapshotState" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "DSSCompleted" PrefixI False) (U1 *)) (C1 * (MetaCons "DSSError'" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DSSPending" PrefixI False) (U1 *)) (C1 * (MetaCons "DSSUnknown" PrefixI False) (U1 *))))

DiskState

data DiskState Source #

Instances

Bounded DiskState Source # 
Enum DiskState Source # 
Eq DiskState Source # 
Data DiskState Source # 

Methods

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

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

toConstr :: DiskState -> Constr #

dataTypeOf :: DiskState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DiskState Source # 
Read DiskState Source # 
Show DiskState Source # 
Generic DiskState Source # 

Associated Types

type Rep DiskState :: * -> * #

Hashable DiskState Source # 
FromJSON DiskState Source # 
NFData DiskState Source # 

Methods

rnf :: DiskState -> () #

ToHeader DiskState Source # 
ToQuery DiskState Source # 
ToByteString DiskState Source # 

Methods

toBS :: DiskState -> ByteString #

FromText DiskState Source # 
ToText DiskState Source # 

Methods

toText :: DiskState -> Text #

type Rep DiskState Source # 
type Rep DiskState = D1 * (MetaData "DiskState" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Available" PrefixI False) (U1 *)) (C1 * (MetaCons "Error'" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "InUse" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Pending" PrefixI False) (U1 *)) (C1 * (MetaCons "Unknown" PrefixI False) (U1 *)))))

InstanceAccessProtocol

data InstanceAccessProtocol Source #

Constructors

Rdp 
SSH 

Instances

Bounded InstanceAccessProtocol Source # 
Enum InstanceAccessProtocol Source # 
Eq InstanceAccessProtocol Source # 
Data InstanceAccessProtocol Source # 

Methods

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

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

toConstr :: InstanceAccessProtocol -> Constr #

dataTypeOf :: InstanceAccessProtocol -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstanceAccessProtocol Source # 
Read InstanceAccessProtocol Source # 
Show InstanceAccessProtocol Source # 
Generic InstanceAccessProtocol Source # 
Hashable InstanceAccessProtocol Source # 
ToJSON InstanceAccessProtocol Source # 
FromJSON InstanceAccessProtocol Source # 
NFData InstanceAccessProtocol Source # 

Methods

rnf :: InstanceAccessProtocol -> () #

ToHeader InstanceAccessProtocol Source # 
ToQuery InstanceAccessProtocol Source # 
ToByteString InstanceAccessProtocol Source # 
FromText InstanceAccessProtocol Source # 
ToText InstanceAccessProtocol Source # 
type Rep InstanceAccessProtocol Source # 
type Rep InstanceAccessProtocol = D1 * (MetaData "InstanceAccessProtocol" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "Rdp" PrefixI False) (U1 *)) (C1 * (MetaCons "SSH" PrefixI False) (U1 *)))

InstanceHealthReason

data InstanceHealthReason Source #

Instances

Bounded InstanceHealthReason Source # 
Enum InstanceHealthReason Source # 
Eq InstanceHealthReason Source # 
Data InstanceHealthReason Source # 

Methods

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

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

toConstr :: InstanceHealthReason -> Constr #

dataTypeOf :: InstanceHealthReason -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceHealthReason -> () #

ToHeader InstanceHealthReason Source # 
ToQuery InstanceHealthReason Source # 
ToByteString InstanceHealthReason Source # 
FromText InstanceHealthReason Source # 
ToText InstanceHealthReason Source # 
type Rep InstanceHealthReason Source # 
type Rep InstanceHealthReason = D1 * (MetaData "InstanceHealthReason" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Instance_DeregistrationInProgress" PrefixI False) (U1 *)) (C1 * (MetaCons "Instance_FailedHealthChecks" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Instance_IPUnusable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Instance_InvalidState" PrefixI False) (U1 *)) (C1 * (MetaCons "Instance_NotInUse" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Instance_NotRegistered" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Instance_ResponseCodeMismatch" PrefixI False) (U1 *)) (C1 * (MetaCons "Instance_Timeout" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Lb_InitialHealthChecking" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Lb_InternalError" PrefixI False) (U1 *)) (C1 * (MetaCons "Lb_RegistrationInProgress" PrefixI False) (U1 *))))))

InstanceHealthState

data InstanceHealthState Source #

Instances

Bounded InstanceHealthState Source # 
Enum InstanceHealthState Source # 
Eq InstanceHealthState Source # 
Data InstanceHealthState Source # 

Methods

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

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

toConstr :: InstanceHealthState -> Constr #

dataTypeOf :: InstanceHealthState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceHealthState -> () #

ToHeader InstanceHealthState Source # 
ToQuery InstanceHealthState Source # 
ToByteString InstanceHealthState Source # 
FromText InstanceHealthState Source # 
ToText InstanceHealthState Source # 
type Rep InstanceHealthState Source # 
type Rep InstanceHealthState = D1 * (MetaData "InstanceHealthState" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Draining" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Healthy" PrefixI False) (U1 *)) (C1 * (MetaCons "Initial" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Unavailable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Unhealthy" PrefixI False) (U1 *)) (C1 * (MetaCons "Unused" PrefixI False) (U1 *)))))

InstanceMetricName

data InstanceMetricName Source #

Instances

Bounded InstanceMetricName Source # 
Enum InstanceMetricName Source # 
Eq InstanceMetricName Source # 
Data InstanceMetricName Source # 

Methods

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

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

toConstr :: InstanceMetricName -> Constr #

dataTypeOf :: InstanceMetricName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstanceMetricName Source # 
Read InstanceMetricName Source # 
Show InstanceMetricName Source # 
Generic InstanceMetricName Source # 
Hashable InstanceMetricName Source # 
ToJSON InstanceMetricName Source # 
FromJSON InstanceMetricName Source # 
NFData InstanceMetricName Source # 

Methods

rnf :: InstanceMetricName -> () #

ToHeader InstanceMetricName Source # 
ToQuery InstanceMetricName Source # 
ToByteString InstanceMetricName Source # 
FromText InstanceMetricName Source # 
ToText InstanceMetricName Source # 
type Rep InstanceMetricName Source # 
type Rep InstanceMetricName = D1 * (MetaData "InstanceMetricName" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CPUUtilization" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NetworkIn" PrefixI False) (U1 *)) (C1 * (MetaCons "NetworkOut" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "StatusCheckFailed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StatusCheckFailedInstance" PrefixI False) (U1 *)) (C1 * (MetaCons "StatusCheckFailedSystem" PrefixI False) (U1 *)))))

InstancePlatform

data InstancePlatform Source #

Constructors

LinuxUnix 
Windows 

Instances

Bounded InstancePlatform Source # 
Enum InstancePlatform Source # 
Eq InstancePlatform Source # 
Data InstancePlatform Source # 

Methods

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

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

toConstr :: InstancePlatform -> Constr #

dataTypeOf :: InstancePlatform -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstancePlatform -> () #

ToHeader InstancePlatform Source # 
ToQuery InstancePlatform Source # 
ToByteString InstancePlatform Source # 
FromText InstancePlatform Source # 
ToText InstancePlatform Source # 
type Rep InstancePlatform Source # 
type Rep InstancePlatform = D1 * (MetaData "InstancePlatform" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "LinuxUnix" PrefixI False) (U1 *)) (C1 * (MetaCons "Windows" PrefixI False) (U1 *)))

InstanceSnapshotState

data InstanceSnapshotState Source #

Instances

Bounded InstanceSnapshotState Source # 
Enum InstanceSnapshotState Source # 
Eq InstanceSnapshotState Source # 
Data InstanceSnapshotState Source # 

Methods

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

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

toConstr :: InstanceSnapshotState -> Constr #

dataTypeOf :: InstanceSnapshotState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceSnapshotState -> () #

ToHeader InstanceSnapshotState Source # 
ToQuery InstanceSnapshotState Source # 
ToByteString InstanceSnapshotState Source # 
FromText InstanceSnapshotState Source # 
ToText InstanceSnapshotState Source # 
type Rep InstanceSnapshotState Source # 
type Rep InstanceSnapshotState = D1 * (MetaData "InstanceSnapshotState" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "ISSAvailable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ISSError'" PrefixI False) (U1 *)) (C1 * (MetaCons "ISSPending" PrefixI False) (U1 *))))

LoadBalancerAttributeName

data LoadBalancerAttributeName Source #

Instances

Bounded LoadBalancerAttributeName Source # 
Enum LoadBalancerAttributeName Source # 
Eq LoadBalancerAttributeName Source # 
Data LoadBalancerAttributeName Source # 

Methods

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

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

toConstr :: LoadBalancerAttributeName -> Constr #

dataTypeOf :: LoadBalancerAttributeName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoadBalancerAttributeName Source # 
Read LoadBalancerAttributeName Source # 
Show LoadBalancerAttributeName Source # 
Generic LoadBalancerAttributeName Source # 
Hashable LoadBalancerAttributeName Source # 
ToJSON LoadBalancerAttributeName Source # 
FromJSON LoadBalancerAttributeName Source # 
NFData LoadBalancerAttributeName Source # 
ToHeader LoadBalancerAttributeName Source # 
ToQuery LoadBalancerAttributeName Source # 
ToByteString LoadBalancerAttributeName Source # 
FromText LoadBalancerAttributeName Source # 
ToText LoadBalancerAttributeName Source # 
type Rep LoadBalancerAttributeName Source # 
type Rep LoadBalancerAttributeName = D1 * (MetaData "LoadBalancerAttributeName" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "HealthCheckPath" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SessionStickinessEnabled" PrefixI False) (U1 *)) (C1 * (MetaCons "SessionStickinessLbCookieDurationSeconds" PrefixI False) (U1 *))))

LoadBalancerMetricName

data LoadBalancerMetricName Source #

Instances

Bounded LoadBalancerMetricName Source # 
Enum LoadBalancerMetricName Source # 
Eq LoadBalancerMetricName Source # 
Data LoadBalancerMetricName Source # 

Methods

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

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

toConstr :: LoadBalancerMetricName -> Constr #

dataTypeOf :: LoadBalancerMetricName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoadBalancerMetricName Source # 
Read LoadBalancerMetricName Source # 
Show LoadBalancerMetricName Source # 
Generic LoadBalancerMetricName Source # 
Hashable LoadBalancerMetricName Source # 
ToJSON LoadBalancerMetricName Source # 
FromJSON LoadBalancerMetricName Source # 
NFData LoadBalancerMetricName Source # 

Methods

rnf :: LoadBalancerMetricName -> () #

ToHeader LoadBalancerMetricName Source # 
ToQuery LoadBalancerMetricName Source # 
ToByteString LoadBalancerMetricName Source # 
FromText LoadBalancerMetricName Source # 
ToText LoadBalancerMetricName Source # 
type Rep LoadBalancerMetricName Source # 
type Rep LoadBalancerMetricName = D1 * (MetaData "LoadBalancerMetricName" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ClientTLSNegotiationErrorCount" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "HTTPCodeInstance2XXCount" PrefixI False) (U1 *)) (C1 * (MetaCons "HTTPCodeInstance3XXCount" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "HTTPCodeInstance4XXCount" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "HTTPCodeInstance5XXCount" PrefixI False) (U1 *)) (C1 * (MetaCons "HTTPCodeLb4XXCount" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "HTTPCodeLb5XXCount" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "HealthyHostCount" PrefixI False) (U1 *)) (C1 * (MetaCons "InstanceResponseTime" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "RejectedConnectionCount" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RequestCount" PrefixI False) (U1 *)) (C1 * (MetaCons "UnhealthyHostCount" PrefixI False) (U1 *))))))

LoadBalancerProtocol

data LoadBalancerProtocol Source #

Constructors

HTTP 
HTTPHTTPS 

Instances

Bounded LoadBalancerProtocol Source # 
Enum LoadBalancerProtocol Source # 
Eq LoadBalancerProtocol Source # 
Data LoadBalancerProtocol Source # 

Methods

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

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

toConstr :: LoadBalancerProtocol -> Constr #

dataTypeOf :: LoadBalancerProtocol -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: LoadBalancerProtocol -> () #

ToHeader LoadBalancerProtocol Source # 
ToQuery LoadBalancerProtocol Source # 
ToByteString LoadBalancerProtocol Source # 
FromText LoadBalancerProtocol Source # 
ToText LoadBalancerProtocol Source # 
type Rep LoadBalancerProtocol Source # 
type Rep LoadBalancerProtocol = D1 * (MetaData "LoadBalancerProtocol" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "HTTP" PrefixI False) (U1 *)) (C1 * (MetaCons "HTTPHTTPS" PrefixI False) (U1 *)))

LoadBalancerState

data LoadBalancerState Source #

Instances

Bounded LoadBalancerState Source # 
Enum LoadBalancerState Source # 
Eq LoadBalancerState Source # 
Data LoadBalancerState Source # 

Methods

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

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

toConstr :: LoadBalancerState -> Constr #

dataTypeOf :: LoadBalancerState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: LoadBalancerState -> () #

ToHeader LoadBalancerState Source # 
ToQuery LoadBalancerState Source # 
ToByteString LoadBalancerState Source # 
FromText LoadBalancerState Source # 
ToText LoadBalancerState Source # 
type Rep LoadBalancerState Source # 
type Rep LoadBalancerState = D1 * (MetaData "LoadBalancerState" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LBSActive" PrefixI False) (U1 *)) (C1 * (MetaCons "LBSActiveImpaired" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LBSFailed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LBSProvisioning" PrefixI False) (U1 *)) (C1 * (MetaCons "LBSUnknown" PrefixI False) (U1 *)))))

LoadBalancerTLSCertificateDomainStatus

data LoadBalancerTLSCertificateDomainStatus Source #

Instances

Bounded LoadBalancerTLSCertificateDomainStatus Source # 
Enum LoadBalancerTLSCertificateDomainStatus Source # 
Eq LoadBalancerTLSCertificateDomainStatus Source # 
Data LoadBalancerTLSCertificateDomainStatus Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateDomainStatus -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateDomainStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoadBalancerTLSCertificateDomainStatus Source # 
Read LoadBalancerTLSCertificateDomainStatus Source # 
Show LoadBalancerTLSCertificateDomainStatus Source # 
Generic LoadBalancerTLSCertificateDomainStatus Source # 
Hashable LoadBalancerTLSCertificateDomainStatus Source # 
FromJSON LoadBalancerTLSCertificateDomainStatus Source # 
NFData LoadBalancerTLSCertificateDomainStatus Source # 
ToHeader LoadBalancerTLSCertificateDomainStatus Source # 
ToQuery LoadBalancerTLSCertificateDomainStatus Source # 
ToByteString LoadBalancerTLSCertificateDomainStatus Source # 
FromText LoadBalancerTLSCertificateDomainStatus Source # 
ToText LoadBalancerTLSCertificateDomainStatus Source # 
type Rep LoadBalancerTLSCertificateDomainStatus Source # 
type Rep LoadBalancerTLSCertificateDomainStatus = D1 * (MetaData "LoadBalancerTLSCertificateDomainStatus" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "LBTCDSFailed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LBTCDSPendingValidation" PrefixI False) (U1 *)) (C1 * (MetaCons "LBTCDSSuccess" PrefixI False) (U1 *))))

LoadBalancerTLSCertificateFailureReason

data LoadBalancerTLSCertificateFailureReason Source #

Instances

Bounded LoadBalancerTLSCertificateFailureReason Source # 
Enum LoadBalancerTLSCertificateFailureReason Source # 
Eq LoadBalancerTLSCertificateFailureReason Source # 
Data LoadBalancerTLSCertificateFailureReason Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateFailureReason -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateFailureReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoadBalancerTLSCertificateFailureReason Source # 
Read LoadBalancerTLSCertificateFailureReason Source # 
Show LoadBalancerTLSCertificateFailureReason Source # 
Generic LoadBalancerTLSCertificateFailureReason Source # 
Hashable LoadBalancerTLSCertificateFailureReason Source # 
FromJSON LoadBalancerTLSCertificateFailureReason Source # 
NFData LoadBalancerTLSCertificateFailureReason Source # 
ToHeader LoadBalancerTLSCertificateFailureReason Source # 
ToQuery LoadBalancerTLSCertificateFailureReason Source # 
ToByteString LoadBalancerTLSCertificateFailureReason Source # 
FromText LoadBalancerTLSCertificateFailureReason Source # 
ToText LoadBalancerTLSCertificateFailureReason Source # 
type Rep LoadBalancerTLSCertificateFailureReason Source # 
type Rep LoadBalancerTLSCertificateFailureReason = D1 * (MetaData "LoadBalancerTLSCertificateFailureReason" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AdditionalVerificationRequired" PrefixI False) (U1 *)) (C1 * (MetaCons "DomainNotAllowed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "InvalidPublicDomain" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NoAvailableContacts" PrefixI False) (U1 *)) (C1 * (MetaCons "Other" PrefixI False) (U1 *)))))

LoadBalancerTLSCertificateRenewalStatus

data LoadBalancerTLSCertificateRenewalStatus Source #

Instances

Bounded LoadBalancerTLSCertificateRenewalStatus Source # 
Enum LoadBalancerTLSCertificateRenewalStatus Source # 
Eq LoadBalancerTLSCertificateRenewalStatus Source # 
Data LoadBalancerTLSCertificateRenewalStatus Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateRenewalStatus -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateRenewalStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoadBalancerTLSCertificateRenewalStatus Source # 
Read LoadBalancerTLSCertificateRenewalStatus Source # 
Show LoadBalancerTLSCertificateRenewalStatus Source # 
Generic LoadBalancerTLSCertificateRenewalStatus Source # 
Hashable LoadBalancerTLSCertificateRenewalStatus Source # 
FromJSON LoadBalancerTLSCertificateRenewalStatus Source # 
NFData LoadBalancerTLSCertificateRenewalStatus Source # 
ToHeader LoadBalancerTLSCertificateRenewalStatus Source # 
ToQuery LoadBalancerTLSCertificateRenewalStatus Source # 
ToByteString LoadBalancerTLSCertificateRenewalStatus Source # 
FromText LoadBalancerTLSCertificateRenewalStatus Source # 
ToText LoadBalancerTLSCertificateRenewalStatus Source # 
type Rep LoadBalancerTLSCertificateRenewalStatus Source # 
type Rep LoadBalancerTLSCertificateRenewalStatus = D1 * (MetaData "LoadBalancerTLSCertificateRenewalStatus" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LBTCRSFailed" PrefixI False) (U1 *)) (C1 * (MetaCons "LBTCRSPendingAutoRenewal" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LBTCRSPendingValidation" PrefixI False) (U1 *)) (C1 * (MetaCons "LBTCRSSuccess" PrefixI False) (U1 *))))

LoadBalancerTLSCertificateRevocationReason

data LoadBalancerTLSCertificateRevocationReason Source #

Instances

Bounded LoadBalancerTLSCertificateRevocationReason Source # 
Enum LoadBalancerTLSCertificateRevocationReason Source # 
Eq LoadBalancerTLSCertificateRevocationReason Source # 
Data LoadBalancerTLSCertificateRevocationReason Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateRevocationReason -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateRevocationReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoadBalancerTLSCertificateRevocationReason Source # 
Read LoadBalancerTLSCertificateRevocationReason Source # 
Show LoadBalancerTLSCertificateRevocationReason Source # 
Generic LoadBalancerTLSCertificateRevocationReason Source # 
Hashable LoadBalancerTLSCertificateRevocationReason Source # 
FromJSON LoadBalancerTLSCertificateRevocationReason Source # 
NFData LoadBalancerTLSCertificateRevocationReason Source # 
ToHeader LoadBalancerTLSCertificateRevocationReason Source # 
ToQuery LoadBalancerTLSCertificateRevocationReason Source # 
ToByteString LoadBalancerTLSCertificateRevocationReason Source # 
FromText LoadBalancerTLSCertificateRevocationReason Source # 
ToText LoadBalancerTLSCertificateRevocationReason Source # 
type Rep LoadBalancerTLSCertificateRevocationReason Source # 
type Rep LoadBalancerTLSCertificateRevocationReason = D1 * (MetaData "LoadBalancerTLSCertificateRevocationReason" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "AACompromise" PrefixI False) (U1 *)) (C1 * (MetaCons "AffiliationChanged" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CaCompromise" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CertificateHold" PrefixI False) (U1 *)) (C1 * (MetaCons "CessationOfOperation" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "KeyCompromise" PrefixI False) (U1 *)) (C1 * (MetaCons "PrivilegeWithdrawn" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "RemoveFromCrl" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Superceded" PrefixI False) (U1 *)) (C1 * (MetaCons "Unspecified" PrefixI False) (U1 *))))))

LoadBalancerTLSCertificateStatus

data LoadBalancerTLSCertificateStatus Source #

Instances

Bounded LoadBalancerTLSCertificateStatus Source # 
Enum LoadBalancerTLSCertificateStatus Source # 
Eq LoadBalancerTLSCertificateStatus Source # 
Data LoadBalancerTLSCertificateStatus Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateStatus -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoadBalancerTLSCertificateStatus Source # 
Read LoadBalancerTLSCertificateStatus Source # 
Show LoadBalancerTLSCertificateStatus Source # 
Generic LoadBalancerTLSCertificateStatus Source # 
Hashable LoadBalancerTLSCertificateStatus Source # 
FromJSON LoadBalancerTLSCertificateStatus Source # 
NFData LoadBalancerTLSCertificateStatus Source # 
ToHeader LoadBalancerTLSCertificateStatus Source # 
ToQuery LoadBalancerTLSCertificateStatus Source # 
ToByteString LoadBalancerTLSCertificateStatus Source # 
FromText LoadBalancerTLSCertificateStatus Source # 
ToText LoadBalancerTLSCertificateStatus Source # 
type Rep LoadBalancerTLSCertificateStatus Source # 
type Rep LoadBalancerTLSCertificateStatus = D1 * (MetaData "LoadBalancerTLSCertificateStatus" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "LBTCSExpired" PrefixI False) (U1 *)) (C1 * (MetaCons "LBTCSFailed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LBTCSInactive" PrefixI False) (U1 *)) (C1 * (MetaCons "LBTCSIssued" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "LBTCSPendingValidation" PrefixI False) (U1 *)) (C1 * (MetaCons "LBTCSRevoked" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LBTCSUnknown" PrefixI False) (U1 *)) (C1 * (MetaCons "LBTCSValidationTimedOut" PrefixI False) (U1 *)))))

MetricStatistic

data MetricStatistic Source #

Instances

Bounded MetricStatistic Source # 
Enum MetricStatistic Source # 
Eq MetricStatistic Source # 
Data MetricStatistic Source # 

Methods

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

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

toConstr :: MetricStatistic -> Constr #

dataTypeOf :: MetricStatistic -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: MetricStatistic -> () #

ToHeader MetricStatistic Source # 
ToQuery MetricStatistic Source # 
ToByteString MetricStatistic Source # 
FromText MetricStatistic Source # 
ToText MetricStatistic Source # 
type Rep MetricStatistic Source # 
type Rep MetricStatistic = D1 * (MetaData "MetricStatistic" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Average" PrefixI False) (U1 *)) (C1 * (MetaCons "Maximum" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Minimum" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SampleCount" PrefixI False) (U1 *)) (C1 * (MetaCons "Sum" PrefixI False) (U1 *)))))

MetricUnit

data MetricUnit Source #

Instances

Bounded MetricUnit Source # 
Enum MetricUnit Source # 
Eq MetricUnit Source # 
Data MetricUnit Source # 

Methods

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

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

toConstr :: MetricUnit -> Constr #

dataTypeOf :: MetricUnit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MetricUnit Source # 
Read MetricUnit Source # 
Show MetricUnit Source # 
Generic MetricUnit Source # 

Associated Types

type Rep MetricUnit :: * -> * #

Hashable MetricUnit Source # 
ToJSON MetricUnit Source # 
FromJSON MetricUnit Source # 
NFData MetricUnit Source # 

Methods

rnf :: MetricUnit -> () #

ToHeader MetricUnit Source # 
ToQuery MetricUnit Source # 
ToByteString MetricUnit Source # 
FromText MetricUnit Source # 
ToText MetricUnit Source # 

Methods

toText :: MetricUnit -> Text #

type Rep MetricUnit Source # 
type Rep MetricUnit = D1 * (MetaData "MetricUnit" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Bits" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "BitsSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "Bytes" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "BytesSecond" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Count" PrefixI False) (U1 *)) (C1 * (MetaCons "CountSecond" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Gigabits" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "GigabitsSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "Gigabytes" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "GigabytesSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "Kilobits" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KilobitsSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "Kilobytes" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KilobytesSecond" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Megabits" PrefixI False) (U1 *)) (C1 * (MetaCons "MegabitsSecond" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Megabytes" PrefixI False) (U1 *)) (C1 * (MetaCons "MegabytesSecond" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Microseconds" PrefixI False) (U1 *)) (C1 * (MetaCons "Milliseconds" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "None" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Percent" PrefixI False) (U1 *)) (C1 * (MetaCons "Seconds" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Terabits" PrefixI False) (U1 *)) (C1 * (MetaCons "TerabitsSecond" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Terabytes" PrefixI False) (U1 *)) (C1 * (MetaCons "TerabytesSecond" PrefixI False) (U1 *)))))))

NetworkProtocol

data NetworkProtocol Source #

Constructors

All 
TCP 
Udp 

Instances

Bounded NetworkProtocol Source # 
Enum NetworkProtocol Source # 
Eq NetworkProtocol Source # 
Data NetworkProtocol Source # 

Methods

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

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

toConstr :: NetworkProtocol -> Constr #

dataTypeOf :: NetworkProtocol -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NetworkProtocol Source # 
Read NetworkProtocol Source # 
Show NetworkProtocol Source # 
Generic NetworkProtocol Source # 
Hashable NetworkProtocol Source # 
ToJSON NetworkProtocol Source # 
FromJSON NetworkProtocol Source # 
NFData NetworkProtocol Source # 

Methods

rnf :: NetworkProtocol -> () #

ToHeader NetworkProtocol Source # 
ToQuery NetworkProtocol Source # 
ToByteString NetworkProtocol Source # 
FromText NetworkProtocol Source # 
ToText NetworkProtocol Source # 
type Rep NetworkProtocol Source # 
type Rep NetworkProtocol = D1 * (MetaData "NetworkProtocol" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "All" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TCP" PrefixI False) (U1 *)) (C1 * (MetaCons "Udp" PrefixI False) (U1 *))))

OperationStatus

data OperationStatus Source #

Instances

Bounded OperationStatus Source # 
Enum OperationStatus Source # 
Eq OperationStatus Source # 
Data OperationStatus Source # 

Methods

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

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

toConstr :: OperationStatus -> Constr #

dataTypeOf :: OperationStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: OperationStatus -> () #

ToHeader OperationStatus Source # 
ToQuery OperationStatus Source # 
ToByteString OperationStatus Source # 
FromText OperationStatus Source # 
ToText OperationStatus Source # 
type Rep OperationStatus Source # 
type Rep OperationStatus = D1 * (MetaData "OperationStatus" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Completed" PrefixI False) (U1 *)) (C1 * (MetaCons "Failed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NotStarted" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Started" PrefixI False) (U1 *)) (C1 * (MetaCons "Succeeded" PrefixI False) (U1 *)))))

OperationType

data OperationType Source #

Instances

Bounded OperationType Source # 
Enum OperationType Source # 
Eq OperationType Source # 
Data OperationType Source # 

Methods

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

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

toConstr :: OperationType -> Constr #

dataTypeOf :: OperationType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OperationType Source # 
Read OperationType Source # 
Show OperationType Source # 
Generic OperationType Source # 

Associated Types

type Rep OperationType :: * -> * #

Hashable OperationType Source # 
FromJSON OperationType Source # 
NFData OperationType Source # 

Methods

rnf :: OperationType -> () #

ToHeader OperationType Source # 
ToQuery OperationType Source # 
ToByteString OperationType Source # 
FromText OperationType Source # 
ToText OperationType Source # 

Methods

toText :: OperationType -> Text #

type Rep OperationType Source # 
type Rep OperationType = D1 * (MetaData "OperationType" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "AllocateStaticIP" PrefixI False) (U1 *)) (C1 * (MetaCons "AttachDisk" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "AttachInstancesToLoadBalancer" PrefixI False) (U1 *)) (C1 * (MetaCons "AttachLoadBalancerTLSCertificate" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "AttachStaticIP" PrefixI False) (U1 *)) (C1 * (MetaCons "CloseInstancePublicPorts" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CreateDisk" PrefixI False) (U1 *)) (C1 * (MetaCons "CreateDiskFromSnapshot" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CreateDiskSnapshot" PrefixI False) (U1 *)) (C1 * (MetaCons "CreateDomain" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CreateInstance" PrefixI False) (U1 *)) (C1 * (MetaCons "CreateInstanceSnapshot" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CreateInstancesFromSnapshot" PrefixI False) (U1 *)) (C1 * (MetaCons "CreateLoadBalancer" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CreateLoadBalancerTLSCertificate" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DeleteDisk" PrefixI False) (U1 *)) (C1 * (MetaCons "DeleteDiskSnapshot" PrefixI False) (U1 *))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DeleteDomain" PrefixI False) (U1 *)) (C1 * (MetaCons "DeleteDomainEntry" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DeleteInstance" PrefixI False) (U1 *)) (C1 * (MetaCons "DeleteInstanceSnapshot" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "DeleteLoadBalancer" PrefixI False) (U1 *)) (C1 * (MetaCons "DeleteLoadBalancerTLSCertificate" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DetachDisk" PrefixI False) (U1 *)) (C1 * (MetaCons "DetachInstancesFromLoadBalancer" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DetachStaticIP" PrefixI False) (U1 *)) (C1 * (MetaCons "OpenInstancePublicPorts" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PutInstancePublicPorts" PrefixI False) (U1 *)) (C1 * (MetaCons "RebootInstance" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "ReleaseStaticIP" PrefixI False) (U1 *)) (C1 * (MetaCons "StartInstance" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "StopInstance" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UpdateDomainEntry" PrefixI False) (U1 *)) (C1 * (MetaCons "UpdateLoadBalancerAttribute" PrefixI False) (U1 *))))))))

PortAccessType

data PortAccessType Source #

Constructors

Private 
Public 

Instances

Bounded PortAccessType Source # 
Enum PortAccessType Source # 
Eq PortAccessType Source # 
Data PortAccessType Source # 

Methods

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

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

toConstr :: PortAccessType -> Constr #

dataTypeOf :: PortAccessType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PortAccessType Source # 
Read PortAccessType Source # 
Show PortAccessType Source # 
Generic PortAccessType Source # 

Associated Types

type Rep PortAccessType :: * -> * #

Hashable PortAccessType Source # 
FromJSON PortAccessType Source # 
NFData PortAccessType Source # 

Methods

rnf :: PortAccessType -> () #

ToHeader PortAccessType Source # 
ToQuery PortAccessType Source # 
ToByteString PortAccessType Source # 
FromText PortAccessType Source # 
ToText PortAccessType Source # 
type Rep PortAccessType Source # 
type Rep PortAccessType = D1 * (MetaData "PortAccessType" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "Private" PrefixI False) (U1 *)) (C1 * (MetaCons "Public" PrefixI False) (U1 *)))

PortState

data PortState Source #

Constructors

Closed 
Open 

Instances

Bounded PortState Source # 
Enum PortState Source # 
Eq PortState Source # 
Data PortState Source # 

Methods

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

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

toConstr :: PortState -> Constr #

dataTypeOf :: PortState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PortState Source # 
Read PortState Source # 
Show PortState Source # 
Generic PortState Source # 

Associated Types

type Rep PortState :: * -> * #

Hashable PortState Source # 
FromJSON PortState Source # 
NFData PortState Source # 

Methods

rnf :: PortState -> () #

ToHeader PortState Source # 
ToQuery PortState Source # 
ToByteString PortState Source # 

Methods

toBS :: PortState -> ByteString #

FromText PortState Source # 
ToText PortState Source # 

Methods

toText :: PortState -> Text #

type Rep PortState Source # 
type Rep PortState = D1 * (MetaData "PortState" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * (C1 * (MetaCons "Closed" PrefixI False) (U1 *)) (C1 * (MetaCons "Open" PrefixI False) (U1 *)))

RegionName

data RegionName Source #

Instances

Bounded RegionName Source # 
Enum RegionName Source # 
Eq RegionName Source # 
Data RegionName Source # 

Methods

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

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

toConstr :: RegionName -> Constr #

dataTypeOf :: RegionName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RegionName Source # 
Read RegionName Source # 
Show RegionName Source # 
Generic RegionName Source # 

Associated Types

type Rep RegionName :: * -> * #

Hashable RegionName Source # 
FromJSON RegionName Source # 
NFData RegionName Source # 

Methods

rnf :: RegionName -> () #

ToHeader RegionName Source # 
ToQuery RegionName Source # 
ToByteString RegionName Source # 
FromText RegionName Source # 
ToText RegionName Source # 

Methods

toText :: RegionName -> Text #

type Rep RegionName Source # 
type Rep RegionName = D1 * (MetaData "RegionName" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ApNortheast1" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ApNortheast2" PrefixI False) (U1 *)) (C1 * (MetaCons "ApSouth1" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ApSoutheast1" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ApSoutheast2" PrefixI False) (U1 *)) (C1 * (MetaCons "EuCentral1" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "EuWest1" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EuWest2" PrefixI False) (U1 *)) (C1 * (MetaCons "UsEast1" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "UsEast2" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UsWest1" PrefixI False) (U1 *)) (C1 * (MetaCons "UsWest2" PrefixI False) (U1 *))))))

ResourceType

data ResourceType Source #

Instances

Bounded ResourceType Source # 
Enum ResourceType Source # 
Eq ResourceType Source # 
Data ResourceType Source # 

Methods

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

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

toConstr :: ResourceType -> Constr #

dataTypeOf :: ResourceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ResourceType Source # 
Read ResourceType Source # 
Show ResourceType Source # 
Generic ResourceType Source # 

Associated Types

type Rep ResourceType :: * -> * #

Hashable ResourceType Source # 
FromJSON ResourceType Source # 
NFData ResourceType Source # 

Methods

rnf :: ResourceType -> () #

ToHeader ResourceType Source # 
ToQuery ResourceType Source # 
ToByteString ResourceType Source # 
FromText ResourceType Source # 
ToText ResourceType Source # 

Methods

toText :: ResourceType -> Text #

type Rep ResourceType Source # 
type Rep ResourceType = D1 * (MetaData "ResourceType" "Network.AWS.Lightsail.Types.Sum" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Disk" PrefixI False) (U1 *)) (C1 * (MetaCons "DiskSnapshot" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Domain" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Instance" PrefixI False) (U1 *)) (C1 * (MetaCons "InstanceSnapshot" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "KeyPair" PrefixI False) (U1 *)) (C1 * (MetaCons "LoadBalancer" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LoadBalancerTLSCertificate" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PeeredVPC" PrefixI False) (U1 *)) (C1 * (MetaCons "StaticIP" PrefixI False) (U1 *))))))

AvailabilityZone

data AvailabilityZone Source #

Describes an Availability Zone.

See: availabilityZone smart constructor.

Instances

Eq AvailabilityZone Source # 
Data AvailabilityZone Source # 

Methods

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

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

toConstr :: AvailabilityZone -> Constr #

dataTypeOf :: AvailabilityZone -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: AvailabilityZone -> () #

type Rep AvailabilityZone Source # 
type Rep AvailabilityZone = D1 * (MetaData "AvailabilityZone" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "AvailabilityZone'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_azState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_azZoneName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

availabilityZone :: AvailabilityZone Source #

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

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

  • azState - The state of the Availability Zone.
  • azZoneName - The name of the Availability Zone. The format is us-east-2a (case-sensitive).

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

The state of the Availability Zone.

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

The name of the Availability Zone. The format is us-east-2a (case-sensitive).

Blueprint

data Blueprint Source #

Describes a blueprint (a virtual private server image).

See: blueprint smart constructor.

Instances

Eq Blueprint Source # 
Data Blueprint Source # 

Methods

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

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

toConstr :: Blueprint -> Constr #

dataTypeOf :: Blueprint -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Blueprint Source # 
Show Blueprint Source # 
Generic Blueprint Source # 

Associated Types

type Rep Blueprint :: * -> * #

Hashable Blueprint Source # 
FromJSON Blueprint Source # 
NFData Blueprint Source # 

Methods

rnf :: Blueprint -> () #

type Rep Blueprint Source # 
type Rep Blueprint = D1 * (MetaData "Blueprint" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "Blueprint'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_bVersionCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstancePlatform))) (S1 * (MetaSel (Just Symbol "_bGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bMinPower") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bProductURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_bLicenseURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_bName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_bBlueprintId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe BlueprintType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bIsActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_bDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

blueprint :: Blueprint Source #

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

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

  • bVersionCode - The version code.
  • bPlatform - The operating system platform (either Linux/Unix-based or Windows Server-based) of the blueprint.
  • bGroup - The group name of the blueprint (e.g., amazon-linux ).
  • bMinPower - The minimum bundle power required to run this blueprint. For example, you need a bundle with a power value of 500 or more to create an instance that uses a blueprint with a minimum power value of 500. 0 indicates that the blueprint runs on all instance sizes.
  • bProductURL - The product URL to learn more about the image or blueprint.
  • bLicenseURL - The end-user license agreement URL for the image or blueprint.
  • bName - The friendly name of the blueprint (e.g., Amazon Linux ).
  • bVersion - The version number of the operating system, application, or stack (e.g., 2016.03.0 ).
  • bBlueprintId - The ID for the virtual private server image (e.g., app_wordpress_4_4 or app_lamp_7_0 ).
  • bType - The type of the blueprint (e.g., os or app ).
  • bIsActive - A Boolean value indicating whether the blueprint is active. When you update your blueprints, you will inactivate old blueprints and keep the most recent versions active.
  • bDescription - The description of the blueprint.

bVersionCode :: Lens' Blueprint (Maybe Text) Source #

The version code.

bPlatform :: Lens' Blueprint (Maybe InstancePlatform) Source #

The operating system platform (either Linux/Unix-based or Windows Server-based) of the blueprint.

bGroup :: Lens' Blueprint (Maybe Text) Source #

The group name of the blueprint (e.g., amazon-linux ).

bMinPower :: Lens' Blueprint (Maybe Int) Source #

The minimum bundle power required to run this blueprint. For example, you need a bundle with a power value of 500 or more to create an instance that uses a blueprint with a minimum power value of 500. 0 indicates that the blueprint runs on all instance sizes.

bProductURL :: Lens' Blueprint (Maybe Text) Source #

The product URL to learn more about the image or blueprint.

bLicenseURL :: Lens' Blueprint (Maybe Text) Source #

The end-user license agreement URL for the image or blueprint.

bName :: Lens' Blueprint (Maybe Text) Source #

The friendly name of the blueprint (e.g., Amazon Linux ).

bVersion :: Lens' Blueprint (Maybe Text) Source #

The version number of the operating system, application, or stack (e.g., 2016.03.0 ).

bBlueprintId :: Lens' Blueprint (Maybe Text) Source #

The ID for the virtual private server image (e.g., app_wordpress_4_4 or app_lamp_7_0 ).

bType :: Lens' Blueprint (Maybe BlueprintType) Source #

The type of the blueprint (e.g., os or app ).

bIsActive :: Lens' Blueprint (Maybe Bool) Source #

A Boolean value indicating whether the blueprint is active. When you update your blueprints, you will inactivate old blueprints and keep the most recent versions active.

bDescription :: Lens' Blueprint (Maybe Text) Source #

The description of the blueprint.

Bundle

data Bundle Source #

Describes a bundle, which is a set of specs describing your virtual private server (or instance ).

See: bundle smart constructor.

Instances

Eq Bundle Source # 

Methods

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

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

Data Bundle Source # 

Methods

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

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

toConstr :: Bundle -> Constr #

dataTypeOf :: Bundle -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Bundle Source # 
Show Bundle Source # 
Generic Bundle Source # 

Associated Types

type Rep Bundle :: * -> * #

Methods

from :: Bundle -> Rep Bundle x #

to :: Rep Bundle x -> Bundle #

Hashable Bundle Source # 

Methods

hashWithSalt :: Int -> Bundle -> Int #

hash :: Bundle -> Int #

FromJSON Bundle Source # 
NFData Bundle Source # 

Methods

rnf :: Bundle -> () #

type Rep Bundle Source # 
type Rep Bundle = D1 * (MetaData "Bundle" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "Bundle'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_bunCpuCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_bunTransferPerMonthInGb") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bunBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bunInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_bunName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_bunPower") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bunDiskSizeInGb") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_bunSupportedPlatforms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [InstancePlatform]))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bunPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bunIsActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_bunRamSizeInGb") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))))))))

bundle :: Bundle Source #

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

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

  • bunCpuCount - The number of vCPUs included in the bundle (e.g., 2 ).
  • bunTransferPerMonthInGb - The data transfer rate per month in GB (e.g., 2000 ).
  • bunBundleId - The bundle ID (e.g., micro_1_0 ).
  • bunInstanceType - The Amazon EC2 instance type (e.g., t2.micro ).
  • bunName - A friendly name for the bundle (e.g., Micro ).
  • bunPower - A numeric value that represents the power of the bundle (e.g., 500 ). You can use the bundle's power value in conjunction with a blueprint's minimum power value to determine whether the blueprint will run on the bundle. For example, you need a bundle with a power value of 500 or more to create an instance that uses a blueprint with a minimum power value of 500.
  • bunDiskSizeInGb - The size of the SSD (e.g., 30 ).
  • bunSupportedPlatforms - The operating system platform (Linux/Unix-based or Windows Server-based) that the bundle supports. You can only launch a WINDOWS bundle on a blueprint that supports the WINDOWS platform. LINUX_UNIX blueprints require a LINUX_UNIX bundle.
  • bunPrice - The price in US dollars (e.g., 5.0 ).
  • bunIsActive - A Boolean value indicating whether the bundle is active.
  • bunRamSizeInGb - The amount of RAM in GB (e.g., 2.0 ).

bunCpuCount :: Lens' Bundle (Maybe Int) Source #

The number of vCPUs included in the bundle (e.g., 2 ).

bunTransferPerMonthInGb :: Lens' Bundle (Maybe Int) Source #

The data transfer rate per month in GB (e.g., 2000 ).

bunBundleId :: Lens' Bundle (Maybe Text) Source #

The bundle ID (e.g., micro_1_0 ).

bunInstanceType :: Lens' Bundle (Maybe Text) Source #

The Amazon EC2 instance type (e.g., t2.micro ).

bunName :: Lens' Bundle (Maybe Text) Source #

A friendly name for the bundle (e.g., Micro ).

bunPower :: Lens' Bundle (Maybe Int) Source #

A numeric value that represents the power of the bundle (e.g., 500 ). You can use the bundle's power value in conjunction with a blueprint's minimum power value to determine whether the blueprint will run on the bundle. For example, you need a bundle with a power value of 500 or more to create an instance that uses a blueprint with a minimum power value of 500.

bunDiskSizeInGb :: Lens' Bundle (Maybe Int) Source #

The size of the SSD (e.g., 30 ).

bunSupportedPlatforms :: Lens' Bundle [InstancePlatform] Source #

The operating system platform (Linux/Unix-based or Windows Server-based) that the bundle supports. You can only launch a WINDOWS bundle on a blueprint that supports the WINDOWS platform. LINUX_UNIX blueprints require a LINUX_UNIX bundle.

bunPrice :: Lens' Bundle (Maybe Double) Source #

The price in US dollars (e.g., 5.0 ).

bunIsActive :: Lens' Bundle (Maybe Bool) Source #

A Boolean value indicating whether the bundle is active.

bunRamSizeInGb :: Lens' Bundle (Maybe Double) Source #

The amount of RAM in GB (e.g., 2.0 ).

Disk

data Disk Source #

Describes a system disk or an block storage disk.

See: disk smart constructor.

Instances

Eq Disk Source # 

Methods

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

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

Data Disk Source # 

Methods

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

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

toConstr :: Disk -> Constr #

dataTypeOf :: Disk -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Disk Source # 
Show Disk Source # 

Methods

showsPrec :: Int -> Disk -> ShowS #

show :: Disk -> String #

showList :: [Disk] -> ShowS #

Generic Disk Source # 

Associated Types

type Rep Disk :: * -> * #

Methods

from :: Disk -> Rep Disk x #

to :: Rep Disk x -> Disk #

Hashable Disk Source # 

Methods

hashWithSalt :: Int -> Disk -> Int #

hash :: Disk -> Int #

FromJSON Disk Source # 
NFData Disk Source # 

Methods

rnf :: Disk -> () #

type Rep Disk Source # 
type Rep Disk = D1 * (MetaData "Disk" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "Disk'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DiskState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))) (S1 * (MetaSel (Just Symbol "_dArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceLocation))) (S1 * (MetaSel (Just Symbol "_dIops") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dIsAttached") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_dAttachmentState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dSizeInGb") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dSupportCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dIsSystemDisk") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dAttachedTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dGbInUse") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))))))

disk :: Disk Source #

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

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

  • dState - Describes the status of the disk.
  • dResourceType - The Lightsail resource type (e.g., Disk ).
  • dArn - The Amazon Resource Name (ARN) of the disk.
  • dPath - The disk path.
  • dCreatedAt - The date when the disk was created.
  • dLocation - The AWS Region and Availability Zone where the disk is located.
  • dIops - The input/output operations per second (IOPS) of the disk.
  • dIsAttached - A Boolean value indicating whether the disk is attached.
  • dAttachmentState - (Deprecated) The attachment state of the disk.
  • dName - The unique name of the disk.
  • dSizeInGb - The size of the disk in GB.
  • dSupportCode - The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.
  • dIsSystemDisk - A Boolean value indicating whether this disk is a system disk (has an operating system loaded on it).
  • dAttachedTo - The resources to which the disk is attached.
  • dGbInUse - (Deprecated) The number of GB in use by the disk.

dState :: Lens' Disk (Maybe DiskState) Source #

Describes the status of the disk.

dResourceType :: Lens' Disk (Maybe ResourceType) Source #

The Lightsail resource type (e.g., Disk ).

dArn :: Lens' Disk (Maybe Text) Source #

The Amazon Resource Name (ARN) of the disk.

dPath :: Lens' Disk (Maybe Text) Source #

The disk path.

dCreatedAt :: Lens' Disk (Maybe UTCTime) Source #

The date when the disk was created.

dLocation :: Lens' Disk (Maybe ResourceLocation) Source #

The AWS Region and Availability Zone where the disk is located.

dIops :: Lens' Disk (Maybe Int) Source #

The input/output operations per second (IOPS) of the disk.

dIsAttached :: Lens' Disk (Maybe Bool) Source #

A Boolean value indicating whether the disk is attached.

dAttachmentState :: Lens' Disk (Maybe Text) Source #

(Deprecated) The attachment state of the disk.

dName :: Lens' Disk (Maybe Text) Source #

The unique name of the disk.

dSizeInGb :: Lens' Disk (Maybe Int) Source #

The size of the disk in GB.

dSupportCode :: Lens' Disk (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

dIsSystemDisk :: Lens' Disk (Maybe Bool) Source #

A Boolean value indicating whether this disk is a system disk (has an operating system loaded on it).

dAttachedTo :: Lens' Disk (Maybe Text) Source #

The resources to which the disk is attached.

dGbInUse :: Lens' Disk (Maybe Int) Source #

(Deprecated) The number of GB in use by the disk.

DiskMap

data DiskMap Source #

Describes a block storage disk mapping.

See: diskMap smart constructor.

Instances

Eq DiskMap Source # 

Methods

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

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

Data DiskMap Source # 

Methods

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

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

toConstr :: DiskMap -> Constr #

dataTypeOf :: DiskMap -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DiskMap Source # 
Show DiskMap Source # 
Generic DiskMap Source # 

Associated Types

type Rep DiskMap :: * -> * #

Methods

from :: DiskMap -> Rep DiskMap x #

to :: Rep DiskMap x -> DiskMap #

Hashable DiskMap Source # 

Methods

hashWithSalt :: Int -> DiskMap -> Int #

hash :: DiskMap -> Int #

ToJSON DiskMap Source # 
NFData DiskMap Source # 

Methods

rnf :: DiskMap -> () #

type Rep DiskMap Source # 
type Rep DiskMap = D1 * (MetaData "DiskMap" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "DiskMap'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_dmNewDiskName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dmOriginalDiskPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

diskMap :: DiskMap Source #

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

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

dmNewDiskName :: Lens' DiskMap (Maybe Text) Source #

The new disk name (e.g., my-new-disk ).

dmOriginalDiskPath :: Lens' DiskMap (Maybe Text) Source #

The original disk path exposed to the instance (for example, devsdh ).

DiskSnapshot

data DiskSnapshot Source #

Describes a block storage disk snapshot.

See: diskSnapshot smart constructor.

Instances

Eq DiskSnapshot Source # 
Data DiskSnapshot Source # 

Methods

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

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

toConstr :: DiskSnapshot -> Constr #

dataTypeOf :: DiskSnapshot -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DiskSnapshot Source # 
Show DiskSnapshot Source # 
Generic DiskSnapshot Source # 

Associated Types

type Rep DiskSnapshot :: * -> * #

Hashable DiskSnapshot Source # 
FromJSON DiskSnapshot Source # 
NFData DiskSnapshot Source # 

Methods

rnf :: DiskSnapshot -> () #

type Rep DiskSnapshot Source # 
type Rep DiskSnapshot = D1 * (MetaData "DiskSnapshot" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "DiskSnapshot'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dsFromDiskName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dsState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DiskSnapshotState)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dsCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dsLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceLocation))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsSizeInGb") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsSupportCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dsFromDiskARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

diskSnapshot :: DiskSnapshot Source #

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

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

  • dsFromDiskName - The unique name of the source disk from which you are creating the disk snapshot.
  • dsState - The status of the disk snapshot operation.
  • dsResourceType - The Lightsail resource type (e.g., DiskSnapshot ).
  • dsArn - The Amazon Resource Name (ARN) of the disk snapshot.
  • dsCreatedAt - The date when the disk snapshot was created.
  • dsLocation - The AWS Region and Availability Zone where the disk snapshot was created.
  • dsProgress - The progress of the disk snapshot operation.
  • dsName - The name of the disk snapshot (e.g., my-disk-snapshot ).
  • dsSizeInGb - The size of the disk in GB.
  • dsSupportCode - The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.
  • dsFromDiskARN - The Amazon Resource Name (ARN) of the source disk from which you are creating the disk snapshot.

dsFromDiskName :: Lens' DiskSnapshot (Maybe Text) Source #

The unique name of the source disk from which you are creating the disk snapshot.

dsState :: Lens' DiskSnapshot (Maybe DiskSnapshotState) Source #

The status of the disk snapshot operation.

dsResourceType :: Lens' DiskSnapshot (Maybe ResourceType) Source #

The Lightsail resource type (e.g., DiskSnapshot ).

dsArn :: Lens' DiskSnapshot (Maybe Text) Source #

The Amazon Resource Name (ARN) of the disk snapshot.

dsCreatedAt :: Lens' DiskSnapshot (Maybe UTCTime) Source #

The date when the disk snapshot was created.

dsLocation :: Lens' DiskSnapshot (Maybe ResourceLocation) Source #

The AWS Region and Availability Zone where the disk snapshot was created.

dsProgress :: Lens' DiskSnapshot (Maybe Text) Source #

The progress of the disk snapshot operation.

dsName :: Lens' DiskSnapshot (Maybe Text) Source #

The name of the disk snapshot (e.g., my-disk-snapshot ).

dsSizeInGb :: Lens' DiskSnapshot (Maybe Int) Source #

The size of the disk in GB.

dsSupportCode :: Lens' DiskSnapshot (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

dsFromDiskARN :: Lens' DiskSnapshot (Maybe Text) Source #

The Amazon Resource Name (ARN) of the source disk from which you are creating the disk snapshot.

Domain

data Domain Source #

Describes a domain where you are storing recordsets in Lightsail.

See: domain smart constructor.

Instances

Eq Domain Source # 

Methods

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

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

Data Domain Source # 

Methods

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

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

toConstr :: Domain -> Constr #

dataTypeOf :: Domain -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Domain Source # 
Show Domain Source # 
Generic Domain Source # 

Associated Types

type Rep Domain :: * -> * #

Methods

from :: Domain -> Rep Domain x #

to :: Rep Domain x -> Domain #

Hashable Domain Source # 

Methods

hashWithSalt :: Int -> Domain -> Int #

hash :: Domain -> Int #

FromJSON Domain Source # 
NFData Domain Source # 

Methods

rnf :: Domain -> () #

type Rep Domain Source # 

domain :: Domain Source #

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

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

  • domResourceType - The resource type.
  • domDomainEntries - An array of key-value pairs containing information about the domain entries.
  • domArn - The Amazon Resource Name (ARN) of the domain recordset (e.g., arn:aws:lightsail:global:123456789101:Domain/824cede0-abc7-4f84-8dbc-12345EXAMPLE ).
  • domCreatedAt - The date when the domain recordset was created.
  • domLocation - The AWS Region and Availability Zones where the domain recordset was created.
  • domName - The name of the domain.
  • domSupportCode - The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

domDomainEntries :: Lens' Domain [DomainEntry] Source #

An array of key-value pairs containing information about the domain entries.

domArn :: Lens' Domain (Maybe Text) Source #

The Amazon Resource Name (ARN) of the domain recordset (e.g., arn:aws:lightsail:global:123456789101:Domain/824cede0-abc7-4f84-8dbc-12345EXAMPLE ).

domCreatedAt :: Lens' Domain (Maybe UTCTime) Source #

The date when the domain recordset was created.

domLocation :: Lens' Domain (Maybe ResourceLocation) Source #

The AWS Region and Availability Zones where the domain recordset was created.

domName :: Lens' Domain (Maybe Text) Source #

The name of the domain.

domSupportCode :: Lens' Domain (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

DomainEntry

data DomainEntry Source #

Describes a domain recordset entry.

See: domainEntry smart constructor.

Instances

Eq DomainEntry Source # 
Data DomainEntry Source # 

Methods

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

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

toConstr :: DomainEntry -> Constr #

dataTypeOf :: DomainEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DomainEntry Source # 
Show DomainEntry Source # 
Generic DomainEntry Source # 

Associated Types

type Rep DomainEntry :: * -> * #

Hashable DomainEntry Source # 
ToJSON DomainEntry Source # 
FromJSON DomainEntry Source # 
NFData DomainEntry Source # 

Methods

rnf :: DomainEntry -> () #

type Rep DomainEntry Source # 

domainEntry :: DomainEntry Source #

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

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

  • deIsAlias - When true , specifies whether the domain entry is an alias used by the Lightsail load balancer. You can include an alias (A type) record in your request, which points to a load balancer DNS name and routes traffic to your load balancer
  • deName - The name of the domain.
  • deId - The ID of the domain recordset entry.
  • deOptions - (Deprecated) The options for the domain entry.
  • deType - The type of domain entry (e.g., SOA or NS ).
  • deTarget - The target AWS name server (e.g., ns-111.awsdns-22.com. ). For Lightsail load balancers, the value looks like ab1234c56789c6b86aba6fb203d443bc-123456789.us-east-2.elb.amazonaws.com . Be sure to also set isAlias to true when setting up an A record for a load balancer.

deIsAlias :: Lens' DomainEntry (Maybe Bool) Source #

When true , specifies whether the domain entry is an alias used by the Lightsail load balancer. You can include an alias (A type) record in your request, which points to a load balancer DNS name and routes traffic to your load balancer

deName :: Lens' DomainEntry (Maybe Text) Source #

The name of the domain.

deId :: Lens' DomainEntry (Maybe Text) Source #

The ID of the domain recordset entry.

deOptions :: Lens' DomainEntry (HashMap Text Text) Source #

(Deprecated) The options for the domain entry.

deType :: Lens' DomainEntry (Maybe Text) Source #

The type of domain entry (e.g., SOA or NS ).

deTarget :: Lens' DomainEntry (Maybe Text) Source #

The target AWS name server (e.g., ns-111.awsdns-22.com. ). For Lightsail load balancers, the value looks like ab1234c56789c6b86aba6fb203d443bc-123456789.us-east-2.elb.amazonaws.com . Be sure to also set isAlias to true when setting up an A record for a load balancer.

Instance

data Instance Source #

Describes an instance (a virtual private server).

See: instance' smart constructor.

Instances

Eq Instance Source # 
Data Instance Source # 

Methods

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

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

toConstr :: Instance -> Constr #

dataTypeOf :: Instance -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Instance Source # 
Show Instance Source # 
Generic Instance Source # 

Associated Types

type Rep Instance :: * -> * #

Methods

from :: Instance -> Rep Instance x #

to :: Rep Instance x -> Instance #

Hashable Instance Source # 

Methods

hashWithSalt :: Int -> Instance -> Int #

hash :: Instance -> Int #

FromJSON Instance Source # 
NFData Instance Source # 

Methods

rnf :: Instance -> () #

type Rep Instance Source # 
type Rep Instance = D1 * (MetaData "Instance" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "Instance'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceState))) (S1 * (MetaSel (Just Symbol "_iIpv6Address") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))) (S1 * (MetaSel (Just Symbol "_iArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_iLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceLocation)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iSshKeyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iUsername") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iNetworking") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceNetworking))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iSupportCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iBlueprintId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iPrivateIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iBlueprintName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iIsStaticIP") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iPublicIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iHardware") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceHardware)))))))))

instance' :: Instance Source #

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

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

  • iState - The status code and the state (e.g., running ) for the instance.
  • iIpv6Address - The IPv6 address of the instance.
  • iResourceType - The type of resource (usually Instance ).
  • iArn - The Amazon Resource Name (ARN) of the instance (e.g., arn:aws:lightsail:us-east-2:123456789101:Instance/244ad76f-8aad-4741-809f-12345EXAMPLE ).
  • iCreatedAt - The timestamp when the instance was created (e.g., 1479734909.17 ).
  • iLocation - The region name and availability zone where the instance is located.
  • iSshKeyName - The name of the SSH key being used to connect to the instance (e.g., LightsailDefaultKeyPair ).
  • iUsername - The user name for connecting to the instance (e.g., ec2-user ).
  • iNetworking - Information about the public ports and monthly data transfer rates for the instance.
  • iBundleId - The bundle for the instance (e.g., micro_1_0 ).
  • iName - The name the user gave the instance (e.g., Amazon_Linux-1GB-Ohio-1 ).
  • iSupportCode - The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.
  • iBlueprintId - The blueprint ID (e.g., os_amlinux_2016_03 ).
  • iPrivateIPAddress - The private IP address of the instance.
  • iBlueprintName - The friendly name of the blueprint (e.g., Amazon Linux ).
  • iIsStaticIP - A Boolean value indicating whether this instance has a static IP assigned to it.
  • iPublicIPAddress - The public IP address of the instance.
  • iHardware - The size of the vCPU and the amount of RAM for the instance.

iState :: Lens' Instance (Maybe InstanceState) Source #

The status code and the state (e.g., running ) for the instance.

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

The IPv6 address of the instance.

iResourceType :: Lens' Instance (Maybe ResourceType) Source #

The type of resource (usually Instance ).

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

The Amazon Resource Name (ARN) of the instance (e.g., arn:aws:lightsail:us-east-2:123456789101:Instance/244ad76f-8aad-4741-809f-12345EXAMPLE ).

iCreatedAt :: Lens' Instance (Maybe UTCTime) Source #

The timestamp when the instance was created (e.g., 1479734909.17 ).

iLocation :: Lens' Instance (Maybe ResourceLocation) Source #

The region name and availability zone where the instance is located.

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

The name of the SSH key being used to connect to the instance (e.g., LightsailDefaultKeyPair ).

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

The user name for connecting to the instance (e.g., ec2-user ).

iNetworking :: Lens' Instance (Maybe InstanceNetworking) Source #

Information about the public ports and monthly data transfer rates for the instance.

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

The bundle for the instance (e.g., micro_1_0 ).

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

The name the user gave the instance (e.g., Amazon_Linux-1GB-Ohio-1 ).

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

The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

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

The blueprint ID (e.g., os_amlinux_2016_03 ).

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

The private IP address of the instance.

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

The friendly name of the blueprint (e.g., Amazon Linux ).

iIsStaticIP :: Lens' Instance (Maybe Bool) Source #

A Boolean value indicating whether this instance has a static IP assigned to it.

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

The public IP address of the instance.

iHardware :: Lens' Instance (Maybe InstanceHardware) Source #

The size of the vCPU and the amount of RAM for the instance.

InstanceAccessDetails

data InstanceAccessDetails Source #

The parameters for gaining temporary access to one of your Amazon Lightsail instances.

See: instanceAccessDetails smart constructor.

Instances

Eq InstanceAccessDetails Source # 
Data InstanceAccessDetails Source # 

Methods

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

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

toConstr :: InstanceAccessDetails -> Constr #

dataTypeOf :: InstanceAccessDetails -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceAccessDetails -> () #

type Rep InstanceAccessDetails Source # 

instanceAccessDetails :: InstanceAccessDetails Source #

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

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

  • iadCertKey - For SSH access, the public key to use when accessing your instance For OpenSSH clients (e.g., command line SSH), you should save this value to tempkey-cert.pub .
  • iadIpAddress - The public IP address of the Amazon Lightsail instance.
  • iadPrivateKey - For SSH access, the temporary private key. For OpenSSH clients (e.g., command line SSH), you should save this value to tempkey ).
  • iadExpiresAt - For SSH access, the date on which the temporary keys expire.
  • iadUsername - The user name to use when logging in to the Amazon Lightsail instance.
  • iadProtocol - The protocol for these Amazon Lightsail instance access details.
  • iadPasswordData - For a Windows Server-based instance, an object with the data you can use to retrieve your password. This is only needed if password is empty and the instance is not new (and therefore the password is not ready yet). When you create an instance, it can take up to 15 minutes for the instance to be ready.
  • iadPassword - For RDP access, the password for your Amazon Lightsail instance. Password will be an empty string if the password for your new instance is not ready yet. When you create an instance, it can take up to 15 minutes for the instance to be ready.
  • iadInstanceName - The name of this Amazon Lightsail instance.

iadCertKey :: Lens' InstanceAccessDetails (Maybe Text) Source #

For SSH access, the public key to use when accessing your instance For OpenSSH clients (e.g., command line SSH), you should save this value to tempkey-cert.pub .

iadIpAddress :: Lens' InstanceAccessDetails (Maybe Text) Source #

The public IP address of the Amazon Lightsail instance.

iadPrivateKey :: Lens' InstanceAccessDetails (Maybe Text) Source #

For SSH access, the temporary private key. For OpenSSH clients (e.g., command line SSH), you should save this value to tempkey ).

iadExpiresAt :: Lens' InstanceAccessDetails (Maybe UTCTime) Source #

For SSH access, the date on which the temporary keys expire.

iadUsername :: Lens' InstanceAccessDetails (Maybe Text) Source #

The user name to use when logging in to the Amazon Lightsail instance.

iadProtocol :: Lens' InstanceAccessDetails (Maybe InstanceAccessProtocol) Source #

The protocol for these Amazon Lightsail instance access details.

iadPasswordData :: Lens' InstanceAccessDetails (Maybe PasswordData) Source #

For a Windows Server-based instance, an object with the data you can use to retrieve your password. This is only needed if password is empty and the instance is not new (and therefore the password is not ready yet). When you create an instance, it can take up to 15 minutes for the instance to be ready.

iadPassword :: Lens' InstanceAccessDetails (Maybe Text) Source #

For RDP access, the password for your Amazon Lightsail instance. Password will be an empty string if the password for your new instance is not ready yet. When you create an instance, it can take up to 15 minutes for the instance to be ready.

iadInstanceName :: Lens' InstanceAccessDetails (Maybe Text) Source #

The name of this Amazon Lightsail instance.

InstanceHardware

data InstanceHardware Source #

Describes the hardware for the instance.

See: instanceHardware smart constructor.

Instances

Eq InstanceHardware Source # 
Data InstanceHardware Source # 

Methods

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

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

toConstr :: InstanceHardware -> Constr #

dataTypeOf :: InstanceHardware -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceHardware -> () #

type Rep InstanceHardware Source # 
type Rep InstanceHardware = D1 * (MetaData "InstanceHardware" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "InstanceHardware'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ihCpuCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ihDisks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Disk]))) (S1 * (MetaSel (Just Symbol "_ihRamSizeInGb") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))))))

instanceHardware :: InstanceHardware Source #

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

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

  • ihCpuCount - The number of vCPUs the instance has.
  • ihDisks - The disks attached to the instance.
  • ihRamSizeInGb - The amount of RAM in GB on the instance (e.g., 1.0 ).

ihCpuCount :: Lens' InstanceHardware (Maybe Int) Source #

The number of vCPUs the instance has.

ihDisks :: Lens' InstanceHardware [Disk] Source #

The disks attached to the instance.

ihRamSizeInGb :: Lens' InstanceHardware (Maybe Double) Source #

The amount of RAM in GB on the instance (e.g., 1.0 ).

InstanceHealthSummary

data InstanceHealthSummary Source #

Describes information about the health of the instance.

See: instanceHealthSummary smart constructor.

Instances

Eq InstanceHealthSummary Source # 
Data InstanceHealthSummary Source # 

Methods

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

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

toConstr :: InstanceHealthSummary -> Constr #

dataTypeOf :: InstanceHealthSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceHealthSummary -> () #

type Rep InstanceHealthSummary Source # 
type Rep InstanceHealthSummary = D1 * (MetaData "InstanceHealthSummary" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "InstanceHealthSummary'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ihsInstanceHealth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceHealthState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ihsInstanceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ihsInstanceHealthReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceHealthReason))))))

instanceHealthSummary :: InstanceHealthSummary Source #

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

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

  • ihsInstanceHealth - Describes the overall instance health. Valid values are below.
  • ihsInstanceName - The name of the Lightsail instance for which you are requesting health check data.
  • ihsInstanceHealthReason - More information about the instance health. If the instanceHealth is healthy , then an instanceHealthReason value is not provided. If instanceHealth is initial , the instanceHealthReason value can be one of the following: * Lb.RegistrationInProgress - The target instance is in the process of being registered with the load balancer. * Lb.InitialHealthChecking - The Lightsail load balancer is still sending the target instance the minimum number of health checks required to determine its health status. If instanceHealth is unhealthy , the instanceHealthReason value can be one of the following: * Instance.ResponseCodeMismatch - The health checks did not return an expected HTTP code. * Instance.Timeout - The health check requests timed out. * Instance.FailedHealthChecks - The health checks failed because the connection to the target instance timed out, the target instance response was malformed, or the target instance failed the health check for an unknown reason. * Lb.InternalError - The health checks failed due to an internal error. If instanceHealth is unused , the instanceHealthReason value can be one of the following: * Instance.NotRegistered - The target instance is not registered with the target group. * Instance.NotInUse - The target group is not used by any load balancer, or the target instance is in an Availability Zone that is not enabled for its load balancer. * Instance.IpUnusable - The target IP address is reserved for use by a Lightsail load balancer. * Instance.InvalidState - The target is in the stopped or terminated state. If instanceHealth is draining , the instanceHealthReason value can be one of the following: * Instance.DeregistrationInProgress - The target instance is in the process of being deregistered and the deregistration delay period has not expired.

ihsInstanceHealth :: Lens' InstanceHealthSummary (Maybe InstanceHealthState) Source #

Describes the overall instance health. Valid values are below.

ihsInstanceName :: Lens' InstanceHealthSummary (Maybe Text) Source #

The name of the Lightsail instance for which you are requesting health check data.

ihsInstanceHealthReason :: Lens' InstanceHealthSummary (Maybe InstanceHealthReason) Source #

More information about the instance health. If the instanceHealth is healthy , then an instanceHealthReason value is not provided. If instanceHealth is initial , the instanceHealthReason value can be one of the following: * Lb.RegistrationInProgress - The target instance is in the process of being registered with the load balancer. * Lb.InitialHealthChecking - The Lightsail load balancer is still sending the target instance the minimum number of health checks required to determine its health status. If instanceHealth is unhealthy , the instanceHealthReason value can be one of the following: * Instance.ResponseCodeMismatch - The health checks did not return an expected HTTP code. * Instance.Timeout - The health check requests timed out. * Instance.FailedHealthChecks - The health checks failed because the connection to the target instance timed out, the target instance response was malformed, or the target instance failed the health check for an unknown reason. * Lb.InternalError - The health checks failed due to an internal error. If instanceHealth is unused , the instanceHealthReason value can be one of the following: * Instance.NotRegistered - The target instance is not registered with the target group. * Instance.NotInUse - The target group is not used by any load balancer, or the target instance is in an Availability Zone that is not enabled for its load balancer. * Instance.IpUnusable - The target IP address is reserved for use by a Lightsail load balancer. * Instance.InvalidState - The target is in the stopped or terminated state. If instanceHealth is draining , the instanceHealthReason value can be one of the following: * Instance.DeregistrationInProgress - The target instance is in the process of being deregistered and the deregistration delay period has not expired.

InstanceNetworking

data InstanceNetworking Source #

Describes monthly data transfer rates and port information for an instance.

See: instanceNetworking smart constructor.

Instances

Eq InstanceNetworking Source # 
Data InstanceNetworking Source # 

Methods

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

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

toConstr :: InstanceNetworking -> Constr #

dataTypeOf :: InstanceNetworking -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceNetworking -> () #

type Rep InstanceNetworking Source # 
type Rep InstanceNetworking = D1 * (MetaData "InstanceNetworking" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "InstanceNetworking'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_inMonthlyTransfer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe MonthlyTransfer))) (S1 * (MetaSel (Just Symbol "_inPorts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [InstancePortInfo])))))

instanceNetworking :: InstanceNetworking Source #

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

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

  • inMonthlyTransfer - The amount of data in GB allocated for monthly data transfers.
  • inPorts - An array of key-value pairs containing information about the ports on the instance.

inMonthlyTransfer :: Lens' InstanceNetworking (Maybe MonthlyTransfer) Source #

The amount of data in GB allocated for monthly data transfers.

inPorts :: Lens' InstanceNetworking [InstancePortInfo] Source #

An array of key-value pairs containing information about the ports on the instance.

InstancePortInfo

data InstancePortInfo Source #

Describes information about the instance ports.

See: instancePortInfo smart constructor.

Instances

Eq InstancePortInfo Source # 
Data InstancePortInfo Source # 

Methods

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

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

toConstr :: InstancePortInfo -> Constr #

dataTypeOf :: InstancePortInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstancePortInfo -> () #

type Rep InstancePortInfo Source # 

instancePortInfo :: InstancePortInfo Source #

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

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

  • ipiFromPort - The first port in the range.
  • ipiCommonName - The common name.
  • ipiProtocol - The protocol being used. Can be one of the following. * tcp - Transmission Control Protocol (TCP) provides reliable, ordered, and error-checked delivery of streamed data between applications running on hosts communicating by an IP network. If you have an application that doesn't require reliable data stream service, use UDP instead. * all - All transport layer protocol types. For more general information, see Transport layer on Wikipedia. * udp - With User Datagram Protocol (UDP), computer applications can send messages (or datagrams) to other hosts on an Internet Protocol (IP) network. Prior communications are not required to set up transmission channels or data paths. Applications that don't require reliable data stream service can use UDP, which provides a connectionless datagram service that emphasizes reduced latency over reliability. If you do require reliable data stream service, use TCP instead.
  • ipiAccessDirection - The access direction (inbound or outbound ).
  • ipiAccessType - The type of access (Public or Private ).
  • ipiToPort - The last port in the range.
  • ipiAccessFrom - The location from which access is allowed (e.g., Anywhere (0.0.0.0/0) ).

ipiFromPort :: Lens' InstancePortInfo (Maybe Natural) Source #

The first port in the range.

ipiProtocol :: Lens' InstancePortInfo (Maybe NetworkProtocol) Source #

The protocol being used. Can be one of the following. * tcp - Transmission Control Protocol (TCP) provides reliable, ordered, and error-checked delivery of streamed data between applications running on hosts communicating by an IP network. If you have an application that doesn't require reliable data stream service, use UDP instead. * all - All transport layer protocol types. For more general information, see Transport layer on Wikipedia. * udp - With User Datagram Protocol (UDP), computer applications can send messages (or datagrams) to other hosts on an Internet Protocol (IP) network. Prior communications are not required to set up transmission channels or data paths. Applications that don't require reliable data stream service can use UDP, which provides a connectionless datagram service that emphasizes reduced latency over reliability. If you do require reliable data stream service, use TCP instead.

ipiAccessDirection :: Lens' InstancePortInfo (Maybe AccessDirection) Source #

The access direction (inbound or outbound ).

ipiAccessType :: Lens' InstancePortInfo (Maybe PortAccessType) Source #

The type of access (Public or Private ).

ipiToPort :: Lens' InstancePortInfo (Maybe Natural) Source #

The last port in the range.

ipiAccessFrom :: Lens' InstancePortInfo (Maybe Text) Source #

The location from which access is allowed (e.g., Anywhere (0.0.0.0/0) ).

InstancePortState

data InstancePortState Source #

Describes the port state.

See: instancePortState smart constructor.

Instances

Eq InstancePortState Source # 
Data InstancePortState Source # 

Methods

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

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

toConstr :: InstancePortState -> Constr #

dataTypeOf :: InstancePortState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstancePortState -> () #

type Rep InstancePortState Source # 
type Rep InstancePortState = D1 * (MetaData "InstancePortState" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "InstancePortState'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ipsFromPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_ipsState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PortState)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ipsProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe NetworkProtocol))) (S1 * (MetaSel (Just Symbol "_ipsToPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))))))

instancePortState :: InstancePortState Source #

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

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

  • ipsFromPort - The first port in the range.
  • ipsState - Specifies whether the instance port is open or closed .
  • ipsProtocol - The protocol being used. Can be one of the following. * tcp - Transmission Control Protocol (TCP) provides reliable, ordered, and error-checked delivery of streamed data between applications running on hosts communicating by an IP network. If you have an application that doesn't require reliable data stream service, use UDP instead. * all - All transport layer protocol types. For more general information, see Transport layer on Wikipedia. * udp - With User Datagram Protocol (UDP), computer applications can send messages (or datagrams) to other hosts on an Internet Protocol (IP) network. Prior communications are not required to set up transmission channels or data paths. Applications that don't require reliable data stream service can use UDP, which provides a connectionless datagram service that emphasizes reduced latency over reliability. If you do require reliable data stream service, use TCP instead.
  • ipsToPort - The last port in the range.

ipsFromPort :: Lens' InstancePortState (Maybe Natural) Source #

The first port in the range.

ipsState :: Lens' InstancePortState (Maybe PortState) Source #

Specifies whether the instance port is open or closed .

ipsProtocol :: Lens' InstancePortState (Maybe NetworkProtocol) Source #

The protocol being used. Can be one of the following. * tcp - Transmission Control Protocol (TCP) provides reliable, ordered, and error-checked delivery of streamed data between applications running on hosts communicating by an IP network. If you have an application that doesn't require reliable data stream service, use UDP instead. * all - All transport layer protocol types. For more general information, see Transport layer on Wikipedia. * udp - With User Datagram Protocol (UDP), computer applications can send messages (or datagrams) to other hosts on an Internet Protocol (IP) network. Prior communications are not required to set up transmission channels or data paths. Applications that don't require reliable data stream service can use UDP, which provides a connectionless datagram service that emphasizes reduced latency over reliability. If you do require reliable data stream service, use TCP instead.

ipsToPort :: Lens' InstancePortState (Maybe Natural) Source #

The last port in the range.

InstanceSnapshot

data InstanceSnapshot Source #

Describes the snapshot of the virtual private server, or instance .

See: instanceSnapshot smart constructor.

Instances

Eq InstanceSnapshot Source # 
Data InstanceSnapshot Source # 

Methods

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

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

toConstr :: InstanceSnapshot -> Constr #

dataTypeOf :: InstanceSnapshot -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceSnapshot -> () #

type Rep InstanceSnapshot Source # 
type Rep InstanceSnapshot = D1 * (MetaData "InstanceSnapshot" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "InstanceSnapshot'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_insFromBlueprintId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_insState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceSnapshotState))) (S1 * (MetaSel (Just Symbol "_insResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_insFromAttachedDisks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Disk]))) (S1 * (MetaSel (Just Symbol "_insArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_insCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_insLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceLocation)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_insProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_insName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_insFromBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_insSizeInGb") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_insSupportCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_insFromInstanceARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_insFromInstanceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

instanceSnapshot :: InstanceSnapshot Source #

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

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

  • insFromBlueprintId - The blueprint ID from which you created the snapshot (e.g., os_debian_8_3 ). A blueprint is a virtual private server (or instance ) image used to create instances quickly.
  • insState - The state the snapshot is in.
  • insResourceType - The type of resource (usually InstanceSnapshot ).
  • insFromAttachedDisks - An array of disk objects containing information about all block storage disks.
  • insArn - The Amazon Resource Name (ARN) of the snapshot (e.g., arn:aws:lightsail:us-east-2:123456789101:InstanceSnapshot/d23b5706-3322-4d83-81e5-12345EXAMPLE ).
  • insCreatedAt - The timestamp when the snapshot was created (e.g., 1479907467.024 ).
  • insLocation - The region name and availability zone where you created the snapshot.
  • insProgress - The progress of the snapshot.
  • insName - The name of the snapshot.
  • insFromBundleId - The bundle ID from which you created the snapshot (e.g., micro_1_0 ).
  • insSizeInGb - The size in GB of the SSD.
  • insSupportCode - The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.
  • insFromInstanceARN - The Amazon Resource Name (ARN) of the instance from which the snapshot was created (e.g., arn:aws:lightsail:us-east-2:123456789101:Instance/64b8404c-ccb1-430b-8daf-12345EXAMPLE ).
  • insFromInstanceName - The instance from which the snapshot was created.

insFromBlueprintId :: Lens' InstanceSnapshot (Maybe Text) Source #

The blueprint ID from which you created the snapshot (e.g., os_debian_8_3 ). A blueprint is a virtual private server (or instance ) image used to create instances quickly.

insResourceType :: Lens' InstanceSnapshot (Maybe ResourceType) Source #

The type of resource (usually InstanceSnapshot ).

insFromAttachedDisks :: Lens' InstanceSnapshot [Disk] Source #

An array of disk objects containing information about all block storage disks.

insArn :: Lens' InstanceSnapshot (Maybe Text) Source #

The Amazon Resource Name (ARN) of the snapshot (e.g., arn:aws:lightsail:us-east-2:123456789101:InstanceSnapshot/d23b5706-3322-4d83-81e5-12345EXAMPLE ).

insCreatedAt :: Lens' InstanceSnapshot (Maybe UTCTime) Source #

The timestamp when the snapshot was created (e.g., 1479907467.024 ).

insLocation :: Lens' InstanceSnapshot (Maybe ResourceLocation) Source #

The region name and availability zone where you created the snapshot.

insProgress :: Lens' InstanceSnapshot (Maybe Text) Source #

The progress of the snapshot.

insName :: Lens' InstanceSnapshot (Maybe Text) Source #

The name of the snapshot.

insFromBundleId :: Lens' InstanceSnapshot (Maybe Text) Source #

The bundle ID from which you created the snapshot (e.g., micro_1_0 ).

insSizeInGb :: Lens' InstanceSnapshot (Maybe Int) Source #

The size in GB of the SSD.

insSupportCode :: Lens' InstanceSnapshot (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

insFromInstanceARN :: Lens' InstanceSnapshot (Maybe Text) Source #

The Amazon Resource Name (ARN) of the instance from which the snapshot was created (e.g., arn:aws:lightsail:us-east-2:123456789101:Instance/64b8404c-ccb1-430b-8daf-12345EXAMPLE ).

insFromInstanceName :: Lens' InstanceSnapshot (Maybe Text) Source #

The instance from which the snapshot was created.

InstanceState

data InstanceState Source #

Describes the virtual private server (or instance ) status.

See: instanceState smart constructor.

Instances

Eq InstanceState Source # 
Data InstanceState Source # 

Methods

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

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

toConstr :: InstanceState -> Constr #

dataTypeOf :: InstanceState -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InstanceState Source # 
Show InstanceState Source # 
Generic InstanceState Source # 

Associated Types

type Rep InstanceState :: * -> * #

Hashable InstanceState Source # 
FromJSON InstanceState Source # 
NFData InstanceState Source # 

Methods

rnf :: InstanceState -> () #

type Rep InstanceState Source # 
type Rep InstanceState = D1 * (MetaData "InstanceState" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "InstanceState'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_isName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_isCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))

instanceState :: InstanceState Source #

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

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

  • isName - The state of the instance (e.g., running or pending ).
  • isCode - The status code for the instance.

isName :: Lens' InstanceState (Maybe Text) Source #

The state of the instance (e.g., running or pending ).

isCode :: Lens' InstanceState (Maybe Int) Source #

The status code for the instance.

KeyPair

data KeyPair Source #

Describes the SSH key pair.

See: keyPair smart constructor.

Instances

Eq KeyPair Source # 

Methods

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

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

Data KeyPair Source # 

Methods

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

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

toConstr :: KeyPair -> Constr #

dataTypeOf :: KeyPair -> DataType #

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

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

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

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

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

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

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

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

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

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

Read KeyPair Source # 
Show KeyPair Source # 
Generic KeyPair Source # 

Associated Types

type Rep KeyPair :: * -> * #

Methods

from :: KeyPair -> Rep KeyPair x #

to :: Rep KeyPair x -> KeyPair #

Hashable KeyPair Source # 

Methods

hashWithSalt :: Int -> KeyPair -> Int #

hash :: KeyPair -> Int #

FromJSON KeyPair Source # 
NFData KeyPair Source # 

Methods

rnf :: KeyPair -> () #

type Rep KeyPair Source # 

keyPair :: KeyPair Source #

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

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

  • kpResourceType - The resource type (usually KeyPair ).
  • kpArn - The Amazon Resource Name (ARN) of the key pair (e.g., arn:aws:lightsail:us-east-2:123456789101:KeyPair/05859e3d-331d-48ba-9034-12345EXAMPLE ).
  • kpCreatedAt - The timestamp when the key pair was created (e.g., 1479816991.349 ).
  • kpLocation - The region name and Availability Zone where the key pair was created.
  • kpFingerprint - The RSA fingerprint of the key pair.
  • kpName - The friendly name of the SSH key pair.
  • kpSupportCode - The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

kpResourceType :: Lens' KeyPair (Maybe ResourceType) Source #

The resource type (usually KeyPair ).

kpArn :: Lens' KeyPair (Maybe Text) Source #

The Amazon Resource Name (ARN) of the key pair (e.g., arn:aws:lightsail:us-east-2:123456789101:KeyPair/05859e3d-331d-48ba-9034-12345EXAMPLE ).

kpCreatedAt :: Lens' KeyPair (Maybe UTCTime) Source #

The timestamp when the key pair was created (e.g., 1479816991.349 ).

kpLocation :: Lens' KeyPair (Maybe ResourceLocation) Source #

The region name and Availability Zone where the key pair was created.

kpFingerprint :: Lens' KeyPair (Maybe Text) Source #

The RSA fingerprint of the key pair.

kpName :: Lens' KeyPair (Maybe Text) Source #

The friendly name of the SSH key pair.

kpSupportCode :: Lens' KeyPair (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

LoadBalancer

data LoadBalancer Source #

Describes the Lightsail load balancer.

See: loadBalancer smart constructor.

Instances

Eq LoadBalancer Source # 
Data LoadBalancer Source # 

Methods

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

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

toConstr :: LoadBalancer -> Constr #

dataTypeOf :: LoadBalancer -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LoadBalancer Source # 
Show LoadBalancer Source # 
Generic LoadBalancer Source # 

Associated Types

type Rep LoadBalancer :: * -> * #

Hashable LoadBalancer Source # 
FromJSON LoadBalancer Source # 
NFData LoadBalancer Source # 

Methods

rnf :: LoadBalancer -> () #

type Rep LoadBalancer Source # 
type Rep LoadBalancer = D1 * (MetaData "LoadBalancer" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "LoadBalancer'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbHealthCheckPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerState))) (S1 * (MetaSel (Just Symbol "_lbResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lbCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceLocation))) (S1 * (MetaSel (Just Symbol "_lbInstancePort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbConfigurationOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map LoadBalancerAttributeName Text)))) (S1 * (MetaSel (Just Symbol "_lbProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerProtocol)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbTlsCertificateSummaries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [LoadBalancerTLSCertificateSummary]))) (S1 * (MetaSel (Just Symbol "_lbName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbSupportCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lbPublicPorts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Nat])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbDnsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lbInstanceHealthSummary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [InstanceHealthSummary]))))))))

loadBalancer :: LoadBalancer Source #

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

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

  • lbHealthCheckPath - The path you specified to perform your health checks. If no path is specified, the load balancer tries to make a request to the default (root) page.
  • lbState - The status of your load balancer. Valid values are below.
  • lbResourceType - The resource type (e.g., LoadBalancer .
  • lbArn - The Amazon Resource Name (ARN) of the load balancer.
  • lbCreatedAt - The date when your load balancer was created.
  • lbLocation - The AWS Region where your load balancer was created (e.g., us-east-2a ). Lightsail automatically creates your load balancer across Availability Zones.
  • lbInstancePort - The port where the load balancer will direct traffic to your Lightsail instances. For HTTP traffic, it's port 80. For HTTPS traffic, it's port 443.
  • lbConfigurationOptions - A string to string map of the configuration options for your load balancer. Valid values are listed below.
  • lbProtocol - The protocol you have enabled for your load balancer. Valid values are below. You can't just have HTTP_HTTPS , but you can have just HTTP .
  • lbTlsCertificateSummaries - An array of LoadBalancerTlsCertificateSummary objects that provide additional information about the SSL/TLS certificates. For example, if true , the certificate is attached to the load balancer.
  • lbName - The name of the load balancer (e.g., my-load-balancer ).
  • lbSupportCode - The support code. Include this code in your email to support when you have questions about your Lightsail load balancer. This code enables our support team to look up your Lightsail information more easily.
  • lbPublicPorts - An array of public port settings for your load balancer. For HTTP, use port 80. For HTTPS, use port 443.
  • lbDnsName - The DNS name of your Lightsail load balancer.
  • lbInstanceHealthSummary - An array of InstanceHealthSummary objects describing the health of the load balancer.

lbHealthCheckPath :: Lens' LoadBalancer (Maybe Text) Source #

The path you specified to perform your health checks. If no path is specified, the load balancer tries to make a request to the default (root) page.

lbState :: Lens' LoadBalancer (Maybe LoadBalancerState) Source #

The status of your load balancer. Valid values are below.

lbResourceType :: Lens' LoadBalancer (Maybe ResourceType) Source #

The resource type (e.g., LoadBalancer .

lbArn :: Lens' LoadBalancer (Maybe Text) Source #

The Amazon Resource Name (ARN) of the load balancer.

lbCreatedAt :: Lens' LoadBalancer (Maybe UTCTime) Source #

The date when your load balancer was created.

lbLocation :: Lens' LoadBalancer (Maybe ResourceLocation) Source #

The AWS Region where your load balancer was created (e.g., us-east-2a ). Lightsail automatically creates your load balancer across Availability Zones.

lbInstancePort :: Lens' LoadBalancer (Maybe Int) Source #

The port where the load balancer will direct traffic to your Lightsail instances. For HTTP traffic, it's port 80. For HTTPS traffic, it's port 443.

lbConfigurationOptions :: Lens' LoadBalancer (HashMap LoadBalancerAttributeName Text) Source #

A string to string map of the configuration options for your load balancer. Valid values are listed below.

lbProtocol :: Lens' LoadBalancer (Maybe LoadBalancerProtocol) Source #

The protocol you have enabled for your load balancer. Valid values are below. You can't just have HTTP_HTTPS , but you can have just HTTP .

lbTlsCertificateSummaries :: Lens' LoadBalancer [LoadBalancerTLSCertificateSummary] Source #

An array of LoadBalancerTlsCertificateSummary objects that provide additional information about the SSL/TLS certificates. For example, if true , the certificate is attached to the load balancer.

lbName :: Lens' LoadBalancer (Maybe Text) Source #

The name of the load balancer (e.g., my-load-balancer ).

lbSupportCode :: Lens' LoadBalancer (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about your Lightsail load balancer. This code enables our support team to look up your Lightsail information more easily.

lbPublicPorts :: Lens' LoadBalancer [Natural] Source #

An array of public port settings for your load balancer. For HTTP, use port 80. For HTTPS, use port 443.

lbDnsName :: Lens' LoadBalancer (Maybe Text) Source #

The DNS name of your Lightsail load balancer.

lbInstanceHealthSummary :: Lens' LoadBalancer [InstanceHealthSummary] Source #

An array of InstanceHealthSummary objects describing the health of the load balancer.

LoadBalancerTLSCertificate

data LoadBalancerTLSCertificate Source #

Describes a load balancer SSL/TLS certificate.

TLS is just an updated, more secure version of Secure Socket Layer (SSL).

See: loadBalancerTLSCertificate smart constructor.

Instances

Eq LoadBalancerTLSCertificate Source # 
Data LoadBalancerTLSCertificate Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificate -> Constr #

dataTypeOf :: LoadBalancerTLSCertificate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LoadBalancerTLSCertificate Source # 
Show LoadBalancerTLSCertificate Source # 
Generic LoadBalancerTLSCertificate Source # 
Hashable LoadBalancerTLSCertificate Source # 
FromJSON LoadBalancerTLSCertificate Source # 
NFData LoadBalancerTLSCertificate Source # 
type Rep LoadBalancerTLSCertificate Source # 
type Rep LoadBalancerTLSCertificate = D1 * (MetaData "LoadBalancerTLSCertificate" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "LoadBalancerTLSCertificate'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcFailureReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerTLSCertificateFailureReason))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcSubject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lbtcStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerTLSCertificateStatus))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcSubjectAlternativeNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))) (S1 * (MetaSel (Just Symbol "_lbtcArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceLocation))) (S1 * (MetaSel (Just Symbol "_lbtcLoadBalancerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcSerial") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcIsAttached") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_lbtcRevokedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcNotBefore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcRevocationReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerTLSCertificateRevocationReason))) (S1 * (MetaSel (Just Symbol "_lbtcDomainName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcRenewalSummary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerTLSCertificateRenewalSummary))) (S1 * (MetaSel (Just Symbol "_lbtcSupportCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcDomainValidationRecords") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [LoadBalancerTLSCertificateDomainValidationRecord]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcIssuedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_lbtcKeyAlgorithm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcSignatureAlgorithm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcIssuer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lbtcNotAfter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))))))

loadBalancerTLSCertificate :: LoadBalancerTLSCertificate Source #

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

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

  • lbtcFailureReason - The reason for the SSL/TLS certificate validation failure.
  • lbtcSubject - The name of the entity that is associated with the public key contained in the certificate.
  • lbtcStatus - The status of the SSL/TLS certificate. Valid values are below.
  • lbtcSubjectAlternativeNames - One or more domains or subdomains included in the certificate. This list contains the domain names that are bound to the public key that is contained in the certificate. The subject alternative names include the canonical domain name (CNAME) of the certificate and additional domain names that can be used to connect to the website, such as example.com , www.example.com , or m.example.com .
  • lbtcResourceType - The resource type (e.g., LoadBalancerTlsCertificate ). * Instance - A Lightsail instance (a virtual private server) * StaticIp - A static IP address * KeyPair - The key pair used to connect to a Lightsail instance * InstanceSnapshot - A Lightsail instance snapshot * Domain - A DNS zone * PeeredVpc - A peered VPC * LoadBalancer - A Lightsail load balancer * LoadBalancerTlsCertificate - An SSL/TLS certificate associated with a Lightsail load balancer * Disk - A Lightsail block storage disk * DiskSnapshot - A block storage disk snapshot
  • lbtcArn - The Amazon Resource Name (ARN) of the SSL/TLS certificate.
  • lbtcCreatedAt - The time when you created your SSL/TLS certificate.
  • lbtcLocation - The AWS Region and Availability Zone where you created your certificate.
  • lbtcLoadBalancerName - The load balancer name where your SSL/TLS certificate is attached.
  • lbtcSerial - The serial number of the certificate.
  • lbtcIsAttached - When true , the SSL/TLS certificate is attached to the Lightsail load balancer.
  • lbtcRevokedAt - The timestamp when the SSL/TLS certificate was revoked.
  • lbtcNotBefore - The timestamp when the SSL/TLS certificate is first valid.
  • lbtcRevocationReason - The reason the certificate was revoked. Valid values are below.
  • lbtcDomainName - The domain name for your SSL/TLS certificate.
  • lbtcName - The name of the SSL/TLS certificate (e.g., my-certificate ).
  • lbtcRenewalSummary - An object containing information about the status of Lightsail's managed renewal for the certificate.
  • lbtcSupportCode - The support code. Include this code in your email to support when you have questions about your Lightsail load balancer or SSL/TLS certificate. This code enables our support team to look up your Lightsail information more easily.
  • lbtcDomainValidationRecords - An array of LoadBalancerTlsCertificateDomainValidationRecord objects describing the records.
  • lbtcIssuedAt - The time when the SSL/TLS certificate was issued.
  • lbtcKeyAlgorithm - The algorithm that was used to generate the key pair (the public and private key).
  • lbtcSignatureAlgorithm - The algorithm that was used to sign the certificate.
  • lbtcIssuer - The issuer of the certificate.
  • lbtcNotAfter - The timestamp when the SSL/TLS certificate expires.

lbtcFailureReason :: Lens' LoadBalancerTLSCertificate (Maybe LoadBalancerTLSCertificateFailureReason) Source #

The reason for the SSL/TLS certificate validation failure.

lbtcSubject :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The name of the entity that is associated with the public key contained in the certificate.

lbtcStatus :: Lens' LoadBalancerTLSCertificate (Maybe LoadBalancerTLSCertificateStatus) Source #

The status of the SSL/TLS certificate. Valid values are below.

lbtcSubjectAlternativeNames :: Lens' LoadBalancerTLSCertificate [Text] Source #

One or more domains or subdomains included in the certificate. This list contains the domain names that are bound to the public key that is contained in the certificate. The subject alternative names include the canonical domain name (CNAME) of the certificate and additional domain names that can be used to connect to the website, such as example.com , www.example.com , or m.example.com .

lbtcResourceType :: Lens' LoadBalancerTLSCertificate (Maybe ResourceType) Source #

The resource type (e.g., LoadBalancerTlsCertificate ). * Instance - A Lightsail instance (a virtual private server) * StaticIp - A static IP address * KeyPair - The key pair used to connect to a Lightsail instance * InstanceSnapshot - A Lightsail instance snapshot * Domain - A DNS zone * PeeredVpc - A peered VPC * LoadBalancer - A Lightsail load balancer * LoadBalancerTlsCertificate - An SSL/TLS certificate associated with a Lightsail load balancer * Disk - A Lightsail block storage disk * DiskSnapshot - A block storage disk snapshot

lbtcArn :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The Amazon Resource Name (ARN) of the SSL/TLS certificate.

lbtcCreatedAt :: Lens' LoadBalancerTLSCertificate (Maybe UTCTime) Source #

The time when you created your SSL/TLS certificate.

lbtcLocation :: Lens' LoadBalancerTLSCertificate (Maybe ResourceLocation) Source #

The AWS Region and Availability Zone where you created your certificate.

lbtcLoadBalancerName :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The load balancer name where your SSL/TLS certificate is attached.

lbtcSerial :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The serial number of the certificate.

lbtcIsAttached :: Lens' LoadBalancerTLSCertificate (Maybe Bool) Source #

When true , the SSL/TLS certificate is attached to the Lightsail load balancer.

lbtcRevokedAt :: Lens' LoadBalancerTLSCertificate (Maybe UTCTime) Source #

The timestamp when the SSL/TLS certificate was revoked.

lbtcNotBefore :: Lens' LoadBalancerTLSCertificate (Maybe UTCTime) Source #

The timestamp when the SSL/TLS certificate is first valid.

lbtcRevocationReason :: Lens' LoadBalancerTLSCertificate (Maybe LoadBalancerTLSCertificateRevocationReason) Source #

The reason the certificate was revoked. Valid values are below.

lbtcDomainName :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The domain name for your SSL/TLS certificate.

lbtcName :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The name of the SSL/TLS certificate (e.g., my-certificate ).

lbtcRenewalSummary :: Lens' LoadBalancerTLSCertificate (Maybe LoadBalancerTLSCertificateRenewalSummary) Source #

An object containing information about the status of Lightsail's managed renewal for the certificate.

lbtcSupportCode :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about your Lightsail load balancer or SSL/TLS certificate. This code enables our support team to look up your Lightsail information more easily.

lbtcDomainValidationRecords :: Lens' LoadBalancerTLSCertificate [LoadBalancerTLSCertificateDomainValidationRecord] Source #

An array of LoadBalancerTlsCertificateDomainValidationRecord objects describing the records.

lbtcIssuedAt :: Lens' LoadBalancerTLSCertificate (Maybe UTCTime) Source #

The time when the SSL/TLS certificate was issued.

lbtcKeyAlgorithm :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The algorithm that was used to generate the key pair (the public and private key).

lbtcSignatureAlgorithm :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The algorithm that was used to sign the certificate.

lbtcIssuer :: Lens' LoadBalancerTLSCertificate (Maybe Text) Source #

The issuer of the certificate.

lbtcNotAfter :: Lens' LoadBalancerTLSCertificate (Maybe UTCTime) Source #

The timestamp when the SSL/TLS certificate expires.

LoadBalancerTLSCertificateDomainValidationOption

data LoadBalancerTLSCertificateDomainValidationOption Source #

Contains information about the domain names on an SSL/TLS certificate that you will use to validate domain ownership.

See: loadBalancerTLSCertificateDomainValidationOption smart constructor.

Instances

Eq LoadBalancerTLSCertificateDomainValidationOption Source # 
Data LoadBalancerTLSCertificateDomainValidationOption Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateDomainValidationOption -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateDomainValidationOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LoadBalancerTLSCertificateDomainValidationOption Source # 
Show LoadBalancerTLSCertificateDomainValidationOption Source # 
Generic LoadBalancerTLSCertificateDomainValidationOption Source # 
Hashable LoadBalancerTLSCertificateDomainValidationOption Source # 
FromJSON LoadBalancerTLSCertificateDomainValidationOption Source # 
NFData LoadBalancerTLSCertificateDomainValidationOption Source # 
type Rep LoadBalancerTLSCertificateDomainValidationOption Source # 
type Rep LoadBalancerTLSCertificateDomainValidationOption = D1 * (MetaData "LoadBalancerTLSCertificateDomainValidationOption" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "LoadBalancerTLSCertificateDomainValidationOption'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcdvoDomainName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lbtcdvoValidationStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerTLSCertificateDomainStatus)))))

loadBalancerTLSCertificateDomainValidationOption :: LoadBalancerTLSCertificateDomainValidationOption Source #

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

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

lbtcdvoDomainName :: Lens' LoadBalancerTLSCertificateDomainValidationOption (Maybe Text) Source #

The fully qualified domain name in the certificate request.

LoadBalancerTLSCertificateDomainValidationRecord

data LoadBalancerTLSCertificateDomainValidationRecord Source #

Describes the validation record of each domain name in the SSL/TLS certificate.

See: loadBalancerTLSCertificateDomainValidationRecord smart constructor.

Instances

Eq LoadBalancerTLSCertificateDomainValidationRecord Source # 
Data LoadBalancerTLSCertificateDomainValidationRecord Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateDomainValidationRecord -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateDomainValidationRecord -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LoadBalancerTLSCertificateDomainValidationRecord Source # 
Show LoadBalancerTLSCertificateDomainValidationRecord Source # 
Generic LoadBalancerTLSCertificateDomainValidationRecord Source # 
Hashable LoadBalancerTLSCertificateDomainValidationRecord Source # 
FromJSON LoadBalancerTLSCertificateDomainValidationRecord Source # 
NFData LoadBalancerTLSCertificateDomainValidationRecord Source # 
type Rep LoadBalancerTLSCertificateDomainValidationRecord Source # 
type Rep LoadBalancerTLSCertificateDomainValidationRecord = D1 * (MetaData "LoadBalancerTLSCertificateDomainValidationRecord" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "LoadBalancerTLSCertificateDomainValidationRecord'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcdvrValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lbtcdvrDomainName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcdvrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcdvrValidationStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerTLSCertificateDomainStatus))) (S1 * (MetaSel (Just Symbol "_lbtcdvrType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

loadBalancerTLSCertificateDomainValidationRecord :: LoadBalancerTLSCertificateDomainValidationRecord Source #

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

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

  • lbtcdvrValue - The value for that type.
  • lbtcdvrDomainName - The domain name against which your SSL/TLS certificate was validated.
  • lbtcdvrName - A fully qualified domain name in the certificate. For example, example.com .
  • lbtcdvrValidationStatus - The validation status. Valid values are listed below.
  • lbtcdvrType - The type of validation record. For example, CNAME for domain validation.

lbtcdvrDomainName :: Lens' LoadBalancerTLSCertificateDomainValidationRecord (Maybe Text) Source #

The domain name against which your SSL/TLS certificate was validated.

lbtcdvrName :: Lens' LoadBalancerTLSCertificateDomainValidationRecord (Maybe Text) Source #

A fully qualified domain name in the certificate. For example, example.com .

lbtcdvrType :: Lens' LoadBalancerTLSCertificateDomainValidationRecord (Maybe Text) Source #

The type of validation record. For example, CNAME for domain validation.

LoadBalancerTLSCertificateRenewalSummary

data LoadBalancerTLSCertificateRenewalSummary Source #

Contains information about the status of Lightsail's managed renewal for the certificate.

See: loadBalancerTLSCertificateRenewalSummary smart constructor.

Instances

Eq LoadBalancerTLSCertificateRenewalSummary Source # 
Data LoadBalancerTLSCertificateRenewalSummary Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateRenewalSummary -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateRenewalSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LoadBalancerTLSCertificateRenewalSummary Source # 
Show LoadBalancerTLSCertificateRenewalSummary Source # 
Generic LoadBalancerTLSCertificateRenewalSummary Source # 
Hashable LoadBalancerTLSCertificateRenewalSummary Source # 
FromJSON LoadBalancerTLSCertificateRenewalSummary Source # 
NFData LoadBalancerTLSCertificateRenewalSummary Source # 
type Rep LoadBalancerTLSCertificateRenewalSummary Source # 
type Rep LoadBalancerTLSCertificateRenewalSummary = D1 * (MetaData "LoadBalancerTLSCertificateRenewalSummary" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "LoadBalancerTLSCertificateRenewalSummary'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcrsRenewalStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LoadBalancerTLSCertificateRenewalStatus))) (S1 * (MetaSel (Just Symbol "_lbtcrsDomainValidationOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [LoadBalancerTLSCertificateDomainValidationOption])))))

loadBalancerTLSCertificateRenewalSummary :: LoadBalancerTLSCertificateRenewalSummary Source #

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

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

  • lbtcrsRenewalStatus - The status of Lightsail's managed renewal of the certificate. Valid values are listed below.
  • lbtcrsDomainValidationOptions - Contains information about the validation of each domain name in the certificate, as it pertains to Lightsail's managed renewal. This is different from the initial validation that occurs as a result of the RequestCertificate request.

lbtcrsRenewalStatus :: Lens' LoadBalancerTLSCertificateRenewalSummary (Maybe LoadBalancerTLSCertificateRenewalStatus) Source #

The status of Lightsail's managed renewal of the certificate. Valid values are listed below.

lbtcrsDomainValidationOptions :: Lens' LoadBalancerTLSCertificateRenewalSummary [LoadBalancerTLSCertificateDomainValidationOption] Source #

Contains information about the validation of each domain name in the certificate, as it pertains to Lightsail's managed renewal. This is different from the initial validation that occurs as a result of the RequestCertificate request.

LoadBalancerTLSCertificateSummary

data LoadBalancerTLSCertificateSummary Source #

Provides a summary of SSL/TLS certificate metadata.

See: loadBalancerTLSCertificateSummary smart constructor.

Instances

Eq LoadBalancerTLSCertificateSummary Source # 
Data LoadBalancerTLSCertificateSummary Source # 

Methods

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

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

toConstr :: LoadBalancerTLSCertificateSummary -> Constr #

dataTypeOf :: LoadBalancerTLSCertificateSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LoadBalancerTLSCertificateSummary Source # 
Show LoadBalancerTLSCertificateSummary Source # 
Generic LoadBalancerTLSCertificateSummary Source # 
Hashable LoadBalancerTLSCertificateSummary Source # 
FromJSON LoadBalancerTLSCertificateSummary Source # 
NFData LoadBalancerTLSCertificateSummary Source # 
type Rep LoadBalancerTLSCertificateSummary Source # 
type Rep LoadBalancerTLSCertificateSummary = D1 * (MetaData "LoadBalancerTLSCertificateSummary" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "LoadBalancerTLSCertificateSummary'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lbtcsIsAttached") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_lbtcsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

loadBalancerTLSCertificateSummary :: LoadBalancerTLSCertificateSummary Source #

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

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

  • lbtcsIsAttached - When true , the SSL/TLS certificate is attached to the Lightsail load balancer.
  • lbtcsName - The name of the SSL/TLS certificate.

lbtcsIsAttached :: Lens' LoadBalancerTLSCertificateSummary (Maybe Bool) Source #

When true , the SSL/TLS certificate is attached to the Lightsail load balancer.

lbtcsName :: Lens' LoadBalancerTLSCertificateSummary (Maybe Text) Source #

The name of the SSL/TLS certificate.

MetricDatapoint

data MetricDatapoint Source #

Describes the metric data point.

See: metricDatapoint smart constructor.

Instances

Eq MetricDatapoint Source # 
Data MetricDatapoint Source # 

Methods

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

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

toConstr :: MetricDatapoint -> Constr #

dataTypeOf :: MetricDatapoint -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: MetricDatapoint -> () #

type Rep MetricDatapoint Source # 

metricDatapoint :: MetricDatapoint Source #

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

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

mdTimestamp :: Lens' MetricDatapoint (Maybe UTCTime) Source #

The timestamp (e.g., 1479816991.349 ).

MonthlyTransfer

data MonthlyTransfer Source #

Describes the monthly data transfer in and out of your virtual private server (or instance ).

See: monthlyTransfer smart constructor.

Instances

Eq MonthlyTransfer Source # 
Data MonthlyTransfer Source # 

Methods

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

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

toConstr :: MonthlyTransfer -> Constr #

dataTypeOf :: MonthlyTransfer -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: MonthlyTransfer -> () #

type Rep MonthlyTransfer Source # 
type Rep MonthlyTransfer = D1 * (MetaData "MonthlyTransfer" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" True) (C1 * (MetaCons "MonthlyTransfer'" PrefixI True) (S1 * (MetaSel (Just Symbol "_mtGbPerMonthAllocated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))))

monthlyTransfer :: MonthlyTransfer Source #

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

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

mtGbPerMonthAllocated :: Lens' MonthlyTransfer (Maybe Int) Source #

The amount allocated per month (in GB).

Operation

data Operation Source #

Describes the API operation.

See: operation smart constructor.

Instances

Eq Operation Source # 
Data Operation Source # 

Methods

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

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

toConstr :: Operation -> Constr #

dataTypeOf :: Operation -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Operation Source # 
Show Operation Source # 
Generic Operation Source # 

Associated Types

type Rep Operation :: * -> * #

Hashable Operation Source # 
FromJSON Operation Source # 
NFData Operation Source # 

Methods

rnf :: Operation -> () #

type Rep Operation Source # 
type Rep Operation = D1 * (MetaData "Operation" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "Operation'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_oStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe OperationStatus))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oOperationDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_oResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oResourceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_oLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceLocation)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_oStatusChangedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oErrorDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_oErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oOperationType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe OperationType))) (S1 * (MetaSel (Just Symbol "_oIsTerminal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))))))

operation :: Operation Source #

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

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

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

The status of the operation.

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

Details about the operation (e.g., Debian-1GB-Ohio-1 ).

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

The timestamp when the operation was initialized (e.g., 1479816991.349 ).

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

The resource name.

oLocation :: Lens' Operation (Maybe ResourceLocation) Source #

The region and Availability Zone.

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

The timestamp when the status was changed (e.g., 1479816991.349 ).

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

The error details.

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

The ID of the operation.

oIsTerminal :: Lens' Operation (Maybe Bool) Source #

A Boolean value indicating whether the operation is terminal.

PasswordData

data PasswordData Source #

The password data for the Windows Server-based instance, including the ciphertext and the key pair name.

See: passwordData smart constructor.

Instances

Eq PasswordData Source # 
Data PasswordData Source # 

Methods

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

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

toConstr :: PasswordData -> Constr #

dataTypeOf :: PasswordData -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PasswordData Source # 
Show PasswordData Source # 
Generic PasswordData Source # 

Associated Types

type Rep PasswordData :: * -> * #

Hashable PasswordData Source # 
FromJSON PasswordData Source # 
NFData PasswordData Source # 

Methods

rnf :: PasswordData -> () #

type Rep PasswordData Source # 
type Rep PasswordData = D1 * (MetaData "PasswordData" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "PasswordData'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pdKeyPairName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_pdCiphertext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

passwordData :: PasswordData Source #

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

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

  • pdKeyPairName - The name of the key pair that you used when creating your instance. If no key pair name was specified when creating the instance, Lightsail uses the default key pair (LightsailDefaultKeyPair ). If you are using a custom key pair, you need to use your own means of decrypting your password using the ciphertext . Lightsail creates the ciphertext by encrypting your password with the public key part of this key pair.
  • pdCiphertext - The encrypted password. Ciphertext will be an empty string if access to your new instance is not ready yet. When you create an instance, it can take up to 15 minutes for the instance to be ready.

pdKeyPairName :: Lens' PasswordData (Maybe Text) Source #

The name of the key pair that you used when creating your instance. If no key pair name was specified when creating the instance, Lightsail uses the default key pair (LightsailDefaultKeyPair ). If you are using a custom key pair, you need to use your own means of decrypting your password using the ciphertext . Lightsail creates the ciphertext by encrypting your password with the public key part of this key pair.

pdCiphertext :: Lens' PasswordData (Maybe Text) Source #

The encrypted password. Ciphertext will be an empty string if access to your new instance is not ready yet. When you create an instance, it can take up to 15 minutes for the instance to be ready.

PortInfo

data PortInfo Source #

Describes information about the ports on your virtual private server (or instance ).

See: portInfo smart constructor.

Instances

Eq PortInfo Source # 
Data PortInfo Source # 

Methods

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

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

toConstr :: PortInfo -> Constr #

dataTypeOf :: PortInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PortInfo Source # 
Show PortInfo Source # 
Generic PortInfo Source # 

Associated Types

type Rep PortInfo :: * -> * #

Methods

from :: PortInfo -> Rep PortInfo x #

to :: Rep PortInfo x -> PortInfo #

Hashable PortInfo Source # 

Methods

hashWithSalt :: Int -> PortInfo -> Int #

hash :: PortInfo -> Int #

ToJSON PortInfo Source # 
NFData PortInfo Source # 

Methods

rnf :: PortInfo -> () #

type Rep PortInfo Source # 
type Rep PortInfo = D1 * (MetaData "PortInfo" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "PortInfo'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_piFromPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_piProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe NetworkProtocol))) (S1 * (MetaSel (Just Symbol "_piToPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))))))

portInfo :: PortInfo Source #

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

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

piFromPort :: Lens' PortInfo (Maybe Natural) Source #

The first port in the range.

piToPort :: Lens' PortInfo (Maybe Natural) Source #

The last port in the range.

RegionInfo

data RegionInfo Source #

Describes the AWS Region.

See: regionInfo smart constructor.

Instances

Eq RegionInfo Source # 
Data RegionInfo Source # 

Methods

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

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RegionInfo #

toConstr :: RegionInfo -> Constr #

dataTypeOf :: RegionInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RegionInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RegionInfo) #

gmapT :: (forall b. Data b => b -> b) -> RegionInfo -> RegionInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RegionInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RegionInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> RegionInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RegionInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RegionInfo -> m RegionInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RegionInfo -> m RegionInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RegionInfo -> m RegionInfo #

Read RegionInfo Source # 
Show RegionInfo Source # 
Generic RegionInfo Source # 

Associated Types

type Rep RegionInfo :: * -> * #

Hashable RegionInfo Source # 
FromJSON RegionInfo Source # 
NFData RegionInfo Source # 

Methods

rnf :: RegionInfo -> () #

type Rep RegionInfo Source # 
type Rep RegionInfo = D1 * (MetaData "RegionInfo" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "RegionInfo'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_riAvailabilityZones") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [AvailabilityZone]))) (S1 * (MetaSel (Just Symbol "_riName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RegionName)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_riDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_riContinentCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_riDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

regionInfo :: RegionInfo Source #

Creates a value of RegionInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • riAvailabilityZones - The Availability Zones. Follows the format us-east-2a (case-sensitive).
  • riName - The region name (e.g., us-east-2 ).
  • riDisplayName - The display name (e.g., Ohio ).
  • riContinentCode - The continent code (e.g., NA , meaning North America).
  • riDescription - The description of the AWS Region (e.g., This region is recommended to serve users in the eastern United States and eastern Canada ).

riAvailabilityZones :: Lens' RegionInfo [AvailabilityZone] Source #

The Availability Zones. Follows the format us-east-2a (case-sensitive).

riName :: Lens' RegionInfo (Maybe RegionName) Source #

The region name (e.g., us-east-2 ).

riDisplayName :: Lens' RegionInfo (Maybe Text) Source #

The display name (e.g., Ohio ).

riContinentCode :: Lens' RegionInfo (Maybe Text) Source #

The continent code (e.g., NA , meaning North America).

riDescription :: Lens' RegionInfo (Maybe Text) Source #

The description of the AWS Region (e.g., This region is recommended to serve users in the eastern United States and eastern Canada ).

ResourceLocation

data ResourceLocation Source #

Describes the resource location.

See: resourceLocation smart constructor.

Instances

Eq ResourceLocation Source # 
Data ResourceLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceLocation -> c ResourceLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceLocation #

toConstr :: ResourceLocation -> Constr #

dataTypeOf :: ResourceLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceLocation) #

gmapT :: (forall b. Data b => b -> b) -> ResourceLocation -> ResourceLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceLocation -> m ResourceLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceLocation -> m ResourceLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceLocation -> m ResourceLocation #

Read ResourceLocation Source # 
Show ResourceLocation Source # 
Generic ResourceLocation Source # 
Hashable ResourceLocation Source # 
FromJSON ResourceLocation Source # 
NFData ResourceLocation Source # 

Methods

rnf :: ResourceLocation -> () #

type Rep ResourceLocation Source # 
type Rep ResourceLocation = D1 * (MetaData "ResourceLocation" "Network.AWS.Lightsail.Types.Product" "amazonka-lightsail-1.6.0-ARMP2uYvcAnENqDU8iFIes" False) (C1 * (MetaCons "ResourceLocation'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rlRegionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RegionName))) (S1 * (MetaSel (Just Symbol "_rlAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

resourceLocation :: ResourceLocation Source #

Creates a value of ResourceLocation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rlAvailabilityZone :: Lens' ResourceLocation (Maybe Text) Source #

The Availability Zone. Follows the format us-east-2a (case-sensitive).

StaticIP

data StaticIP Source #

Describes the static IP.

See: staticIP smart constructor.

Instances

Eq StaticIP Source # 
Data StaticIP Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StaticIP -> c StaticIP #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StaticIP #

toConstr :: StaticIP -> Constr #

dataTypeOf :: StaticIP -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StaticIP) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StaticIP) #

gmapT :: (forall b. Data b => b -> b) -> StaticIP -> StaticIP #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StaticIP -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StaticIP -> r #

gmapQ :: (forall d. Data d => d -> u) -> StaticIP -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StaticIP -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StaticIP -> m StaticIP #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticIP -> m StaticIP #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticIP -> m StaticIP #

Read StaticIP Source # 
Show StaticIP Source # 
Generic StaticIP Source # 

Associated Types

type Rep StaticIP :: * -> * #

Methods

from :: StaticIP -> Rep StaticIP x #

to :: Rep StaticIP x -> StaticIP #

Hashable StaticIP Source # 

Methods

hashWithSalt :: Int -> StaticIP -> Int #

hash :: StaticIP -> Int #

FromJSON StaticIP Source # 
NFData StaticIP Source # 

Methods

rnf :: StaticIP -> () #

type Rep StaticIP Source # 

staticIP :: StaticIP Source #

Creates a value of StaticIP with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • siIpAddress - The static IP address.
  • siResourceType - The resource type (usually StaticIp ).
  • siArn - The Amazon Resource Name (ARN) of the static IP (e.g., arn:aws:lightsail:us-east-2:123456789101:StaticIp/9cbb4a9e-f8e3-4dfe-b57e-12345EXAMPLE ).
  • siCreatedAt - The timestamp when the static IP was created (e.g., 1479735304.222 ).
  • siLocation - The region and Availability Zone where the static IP was created.
  • siIsAttached - A Boolean value indicating whether the static IP is attached.
  • siName - The name of the static IP (e.g., StaticIP-Ohio-EXAMPLE ).
  • siSupportCode - The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.
  • siAttachedTo - The instance where the static IP is attached (e.g., Amazon_Linux-1GB-Ohio-1 ).

siIpAddress :: Lens' StaticIP (Maybe Text) Source #

The static IP address.

siResourceType :: Lens' StaticIP (Maybe ResourceType) Source #

The resource type (usually StaticIp ).

siArn :: Lens' StaticIP (Maybe Text) Source #

The Amazon Resource Name (ARN) of the static IP (e.g., arn:aws:lightsail:us-east-2:123456789101:StaticIp/9cbb4a9e-f8e3-4dfe-b57e-12345EXAMPLE ).

siCreatedAt :: Lens' StaticIP (Maybe UTCTime) Source #

The timestamp when the static IP was created (e.g., 1479735304.222 ).

siLocation :: Lens' StaticIP (Maybe ResourceLocation) Source #

The region and Availability Zone where the static IP was created.

siIsAttached :: Lens' StaticIP (Maybe Bool) Source #

A Boolean value indicating whether the static IP is attached.

siName :: Lens' StaticIP (Maybe Text) Source #

The name of the static IP (e.g., StaticIP-Ohio-EXAMPLE ).

siSupportCode :: Lens' StaticIP (Maybe Text) Source #

The support code. Include this code in your email to support when you have questions about an instance or another resource in Lightsail. This code enables our support team to look up your Lightsail information more easily.

siAttachedTo :: Lens' StaticIP (Maybe Text) Source #

The instance where the static IP is attached (e.g., Amazon_Linux-1GB-Ohio-1 ).