amazonka-gamelift-1.4.5: Amazon GameLift SDK.

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

Network.AWS.GameLift.Types

Contents

Description

 

Synopsis

Service Configuration

gameLift :: Service Source #

API version 2015-10-01 of the Amazon GameLift SDK configuration.

Errors

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

The requested operation would cause a conflict with the current state of a resource associated with the request and/or the fleet. Resolve the conflict before retrying.

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

One or more parameter values in the request are invalid. Correct the invalid parameter values before retrying.

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

The requested operation would cause a conflict with the current state of a service resource associated with the request. Resolve the conflict before retrying this request.

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

The service is unable to resolve the routing for a particular alias because it has a terminal RoutingStrategy associated with it. The message returned in this exception is the message defined in the routing strategy itself. Such requests should only be retried if the routing strategy for the specified alias is modified.

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

A service resource associated with the request could not be found. Clients should not retry such requests.

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

The game instance is currently full and cannot allow the requested player(s) to join. Clients can retry such requests immediately or after a waiting period.

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

The requested operation would cause a conflict with the current state of a resource associated with the request and/or the game instance. Resolve the conflict before retrying.

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

The service encountered an unrecoverable internal failure while processing the request. Clients can retry such requests immediately or after a waiting period.

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

A game session with this custom ID string already exists in this fleet. Resolve this conflict before retrying this request.

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

The client failed authentication. Clients should not retry such requests.

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

The specified fleet has no available instances to fulfill a CreateGameSession request. Clients can retry such requests immediately or after a waiting period.

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

The requested operation would cause the resource to exceed the allowed service limit. Resolve the issue before retrying.

BuildStatus

data BuildStatus Source #

Constructors

Failed 
Initialized 
Ready 

Instances

Bounded BuildStatus Source # 
Enum BuildStatus Source # 
Eq BuildStatus Source # 
Data BuildStatus Source # 

Methods

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

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

toConstr :: BuildStatus -> Constr #

dataTypeOf :: BuildStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BuildStatus Source # 
Read BuildStatus Source # 
Show BuildStatus Source # 
Generic BuildStatus Source # 

Associated Types

type Rep BuildStatus :: * -> * #

Hashable BuildStatus Source # 
ToJSON BuildStatus Source # 
FromJSON BuildStatus Source # 
NFData BuildStatus Source # 

Methods

rnf :: BuildStatus -> () #

ToHeader BuildStatus Source # 
ToQuery BuildStatus Source # 
ToByteString BuildStatus Source # 
FromText BuildStatus Source # 
ToText BuildStatus Source # 

Methods

toText :: BuildStatus -> Text #

type Rep BuildStatus Source # 
type Rep BuildStatus = D1 (MetaData "BuildStatus" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "Failed" PrefixI False) U1) ((:+:) (C1 (MetaCons "Initialized" PrefixI False) U1) (C1 (MetaCons "Ready" PrefixI False) U1)))

ComparisonOperatorType

data ComparisonOperatorType Source #

Instances

Bounded ComparisonOperatorType Source # 
Enum ComparisonOperatorType Source # 
Eq ComparisonOperatorType Source # 
Data ComparisonOperatorType Source # 

Methods

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

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

toConstr :: ComparisonOperatorType -> Constr #

dataTypeOf :: ComparisonOperatorType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ComparisonOperatorType -> () #

ToHeader ComparisonOperatorType Source # 
ToQuery ComparisonOperatorType Source # 
ToByteString ComparisonOperatorType Source # 
FromText ComparisonOperatorType Source # 
ToText ComparisonOperatorType Source # 
type Rep ComparisonOperatorType Source # 
type Rep ComparisonOperatorType = D1 (MetaData "ComparisonOperatorType" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) (C1 (MetaCons "GreaterThanOrEqualToThreshold" PrefixI False) U1) (C1 (MetaCons "GreaterThanThreshold" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LessThanOrEqualToThreshold" PrefixI False) U1) (C1 (MetaCons "LessThanThreshold" PrefixI False) U1)))

EC2InstanceType

data EC2InstanceType Source #

Instances

Bounded EC2InstanceType Source # 
Enum EC2InstanceType Source # 
Eq EC2InstanceType Source # 
Data EC2InstanceType Source # 

Methods

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

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

toConstr :: EC2InstanceType -> Constr #

dataTypeOf :: EC2InstanceType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EC2InstanceType -> () #

ToHeader EC2InstanceType Source # 
ToQuery EC2InstanceType Source # 
ToByteString EC2InstanceType Source # 
FromText EC2InstanceType Source # 
ToText EC2InstanceType Source # 
type Rep EC2InstanceType Source # 
type Rep EC2InstanceType = D1 (MetaData "EC2InstanceType" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "C3_2XLarge" PrefixI False) U1) ((:+:) (C1 (MetaCons "C3_4XLarge" PrefixI False) U1) (C1 (MetaCons "C3_8XLarge" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "C3_Large" PrefixI False) U1) (C1 (MetaCons "C3_XLarge" PrefixI False) U1)) ((:+:) (C1 (MetaCons "C4_2XLarge" PrefixI False) U1) (C1 (MetaCons "C4_4XLarge" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "C4_8XLarge" PrefixI False) U1) ((:+:) (C1 (MetaCons "C4_Large" PrefixI False) U1) (C1 (MetaCons "C4_XLarge" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "M3_2XLarge" PrefixI False) U1) (C1 (MetaCons "M3_Large" PrefixI False) U1)) ((:+:) (C1 (MetaCons "M3_Medium" PrefixI False) U1) (C1 (MetaCons "M3_XLarge" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "M4_10XLarge" PrefixI False) U1) ((:+:) (C1 (MetaCons "M4_2XLarge" PrefixI False) U1) (C1 (MetaCons "M4_4XLarge" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "M4_Large" PrefixI False) U1) (C1 (MetaCons "M4_XLarge" PrefixI False) U1)) ((:+:) (C1 (MetaCons "R3_2XLarge" PrefixI False) U1) (C1 (MetaCons "R3_4XLarge" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "R3_8XLarge" PrefixI False) U1) ((:+:) (C1 (MetaCons "R3_Large" PrefixI False) U1) (C1 (MetaCons "R3_XLarge" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "T2_Large" PrefixI False) U1) (C1 (MetaCons "T2_Medium" PrefixI False) U1)) ((:+:) (C1 (MetaCons "T2_Micro" PrefixI False) U1) (C1 (MetaCons "T2_Small" PrefixI False) U1))))))

EventCode

data EventCode Source #

Instances

Bounded EventCode Source # 
Enum EventCode Source # 
Eq EventCode Source # 
Data EventCode Source # 

Methods

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

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

toConstr :: EventCode -> Constr #

dataTypeOf :: EventCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventCode Source # 
Read EventCode Source # 
Show EventCode Source # 
Generic EventCode Source # 

Associated Types

type Rep EventCode :: * -> * #

Hashable EventCode Source # 
FromJSON EventCode Source # 
NFData EventCode Source # 

Methods

rnf :: EventCode -> () #

ToHeader EventCode Source # 
ToQuery EventCode Source # 
ToByteString EventCode Source # 

Methods

toBS :: EventCode -> ByteString #

FromText EventCode Source # 
ToText EventCode Source # 

Methods

toText :: EventCode -> Text #

type Rep EventCode Source # 
type Rep EventCode = D1 (MetaData "EventCode" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FleetActivationFailed" PrefixI False) U1) ((:+:) (C1 (MetaCons "FleetActivationFailedNoInstances" PrefixI False) U1) (C1 (MetaCons "FleetBinaryDownloadFailed" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FleetCreated" PrefixI False) U1) ((:+:) (C1 (MetaCons "FleetDeleted" PrefixI False) U1) (C1 (MetaCons "FleetInitializationFailed" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "FleetNewGameSessionProtectionPolicyUpdated" PrefixI False) U1) ((:+:) (C1 (MetaCons "FleetScalingEvent" PrefixI False) U1) (C1 (MetaCons "FleetStateActivating" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FleetStateActive" PrefixI False) U1) ((:+:) (C1 (MetaCons "FleetStateBuilding" PrefixI False) U1) (C1 (MetaCons "FleetStateDownloading" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FleetStateError" PrefixI False) U1) ((:+:) (C1 (MetaCons "FleetStateValidating" PrefixI False) U1) (C1 (MetaCons "FleetValidationExecutableRuntimeFailure" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FleetValidationLaunchPathNotFound" PrefixI False) U1) ((:+:) (C1 (MetaCons "FleetValidationTimedOut" PrefixI False) U1) (C1 (MetaCons "GenericEvent" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "ServerProcessCrashed" PrefixI False) U1) ((:+:) (C1 (MetaCons "ServerProcessForceTerminated" PrefixI False) U1) (C1 (MetaCons "ServerProcessInvalidPath" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "ServerProcessProcessExitTimeout" PrefixI False) U1) (C1 (MetaCons "ServerProcessProcessReadyTimeout" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ServerProcessSDKInitializationTimeout" PrefixI False) U1) (C1 (MetaCons "ServerProcessTerminatedUnhealthy" PrefixI False) U1))))))

FleetStatus

data FleetStatus Source #

Instances

Bounded FleetStatus Source # 
Enum FleetStatus Source # 
Eq FleetStatus Source # 
Data FleetStatus Source # 

Methods

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

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

toConstr :: FleetStatus -> Constr #

dataTypeOf :: FleetStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FleetStatus Source # 
Read FleetStatus Source # 
Show FleetStatus Source # 
Generic FleetStatus Source # 

Associated Types

type Rep FleetStatus :: * -> * #

Hashable FleetStatus Source # 
FromJSON FleetStatus Source # 
NFData FleetStatus Source # 

Methods

rnf :: FleetStatus -> () #

ToHeader FleetStatus Source # 
ToQuery FleetStatus Source # 
ToByteString FleetStatus Source # 
FromText FleetStatus Source # 
ToText FleetStatus Source # 

Methods

toText :: FleetStatus -> Text #

type Rep FleetStatus Source # 
type Rep FleetStatus = D1 (MetaData "FleetStatus" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FSActivating" PrefixI False) U1) (C1 (MetaCons "FSActive" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FSBuilding" PrefixI False) U1) (C1 (MetaCons "FSDeleting" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "FSDownloading" PrefixI False) U1) (C1 (MetaCons "FSError'" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FSNew" PrefixI False) U1) ((:+:) (C1 (MetaCons "FSTerminated" PrefixI False) U1) (C1 (MetaCons "FSValidating" PrefixI False) U1)))))

GameSessionStatus

data GameSessionStatus Source #

Instances

Bounded GameSessionStatus Source # 
Enum GameSessionStatus Source # 
Eq GameSessionStatus Source # 
Data GameSessionStatus Source # 

Methods

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

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

toConstr :: GameSessionStatus -> Constr #

dataTypeOf :: GameSessionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GameSessionStatus -> () #

ToHeader GameSessionStatus Source # 
ToQuery GameSessionStatus Source # 
ToByteString GameSessionStatus Source # 
FromText GameSessionStatus Source # 
ToText GameSessionStatus Source # 
type Rep GameSessionStatus Source # 
type Rep GameSessionStatus = D1 (MetaData "GameSessionStatus" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) (C1 (MetaCons "GSSActivating" PrefixI False) U1) (C1 (MetaCons "GSSActive" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GSSError'" PrefixI False) U1) ((:+:) (C1 (MetaCons "GSSTerminated" PrefixI False) U1) (C1 (MetaCons "GSSTerminating" PrefixI False) U1))))

IPProtocol

data IPProtocol Source #

Constructors

TCP 
Udp 

Instances

Bounded IPProtocol Source # 
Enum IPProtocol Source # 
Eq IPProtocol Source # 
Data IPProtocol Source # 

Methods

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

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

toConstr :: IPProtocol -> Constr #

dataTypeOf :: IPProtocol -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IPProtocol Source # 
Read IPProtocol Source # 
Show IPProtocol Source # 
Generic IPProtocol Source # 

Associated Types

type Rep IPProtocol :: * -> * #

Hashable IPProtocol Source # 
ToJSON IPProtocol Source # 
FromJSON IPProtocol Source # 
NFData IPProtocol Source # 

Methods

rnf :: IPProtocol -> () #

ToHeader IPProtocol Source # 
ToQuery IPProtocol Source # 
ToByteString IPProtocol Source # 
FromText IPProtocol Source # 
ToText IPProtocol Source # 

Methods

toText :: IPProtocol -> Text #

type Rep IPProtocol Source # 
type Rep IPProtocol = D1 (MetaData "IPProtocol" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "TCP" PrefixI False) U1) (C1 (MetaCons "Udp" PrefixI False) U1))

InstanceStatus

data InstanceStatus Source #

Instances

Bounded InstanceStatus Source # 
Enum InstanceStatus Source # 
Eq InstanceStatus Source # 
Data InstanceStatus Source # 

Methods

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

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

toConstr :: InstanceStatus -> Constr #

dataTypeOf :: InstanceStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstanceStatus Source # 
Read InstanceStatus Source # 
Show InstanceStatus Source # 
Generic InstanceStatus Source # 

Associated Types

type Rep InstanceStatus :: * -> * #

Hashable InstanceStatus Source # 
FromJSON InstanceStatus Source # 
NFData InstanceStatus Source # 

Methods

rnf :: InstanceStatus -> () #

ToHeader InstanceStatus Source # 
ToQuery InstanceStatus Source # 
ToByteString InstanceStatus Source # 
FromText InstanceStatus Source # 
ToText InstanceStatus Source # 
type Rep InstanceStatus Source # 
type Rep InstanceStatus = D1 (MetaData "InstanceStatus" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "ISActive" PrefixI False) U1) ((:+:) (C1 (MetaCons "ISPending" PrefixI False) U1) (C1 (MetaCons "ISTerminating" PrefixI False) U1)))

MetricName

data MetricName Source #

Instances

Bounded MetricName Source # 
Enum MetricName Source # 
Eq MetricName Source # 
Data MetricName Source # 

Methods

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

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

toConstr :: MetricName -> Constr #

dataTypeOf :: MetricName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MetricName Source # 
Read MetricName Source # 
Show MetricName Source # 
Generic MetricName Source # 

Associated Types

type Rep MetricName :: * -> * #

Hashable MetricName Source # 
ToJSON MetricName Source # 
FromJSON MetricName Source # 
NFData MetricName Source # 

Methods

rnf :: MetricName -> () #

ToHeader MetricName Source # 
ToQuery MetricName Source # 
ToByteString MetricName Source # 
FromText MetricName Source # 
ToText MetricName Source # 

Methods

toText :: MetricName -> Text #

type Rep MetricName Source # 
type Rep MetricName = D1 (MetaData "MetricName" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) (C1 (MetaCons "ActivatingGameSessions" PrefixI False) U1) ((:+:) (C1 (MetaCons "ActiveGameSessions" PrefixI False) U1) (C1 (MetaCons "ActiveInstances" PrefixI False) U1))) ((:+:) (C1 (MetaCons "AvailablePlayerSessions" PrefixI False) U1) ((:+:) (C1 (MetaCons "CurrentPlayerSessions" PrefixI False) U1) (C1 (MetaCons "IdleInstances" PrefixI False) U1))))

OperatingSystem

data OperatingSystem Source #

Constructors

AmazonLinux 
Windows2012 

Instances

Bounded OperatingSystem Source # 
Enum OperatingSystem Source # 
Eq OperatingSystem Source # 
Data OperatingSystem Source # 

Methods

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

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

toConstr :: OperatingSystem -> Constr #

dataTypeOf :: OperatingSystem -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: OperatingSystem -> () #

ToHeader OperatingSystem Source # 
ToQuery OperatingSystem Source # 
ToByteString OperatingSystem Source # 
FromText OperatingSystem Source # 
ToText OperatingSystem Source # 
type Rep OperatingSystem Source # 
type Rep OperatingSystem = D1 (MetaData "OperatingSystem" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "AmazonLinux" PrefixI False) U1) (C1 (MetaCons "Windows2012" PrefixI False) U1))

PlayerSessionCreationPolicy

data PlayerSessionCreationPolicy Source #

Constructors

AcceptAll 
DenyAll 

Instances

Bounded PlayerSessionCreationPolicy Source # 
Enum PlayerSessionCreationPolicy Source # 
Eq PlayerSessionCreationPolicy Source # 
Data PlayerSessionCreationPolicy Source # 

Methods

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

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

toConstr :: PlayerSessionCreationPolicy -> Constr #

dataTypeOf :: PlayerSessionCreationPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PlayerSessionCreationPolicy Source # 
Read PlayerSessionCreationPolicy Source # 
Show PlayerSessionCreationPolicy Source # 
Generic PlayerSessionCreationPolicy Source # 
Hashable PlayerSessionCreationPolicy Source # 
ToJSON PlayerSessionCreationPolicy Source # 
FromJSON PlayerSessionCreationPolicy Source # 
NFData PlayerSessionCreationPolicy Source # 
ToHeader PlayerSessionCreationPolicy Source # 
ToQuery PlayerSessionCreationPolicy Source # 
ToByteString PlayerSessionCreationPolicy Source # 
FromText PlayerSessionCreationPolicy Source # 
ToText PlayerSessionCreationPolicy Source # 
type Rep PlayerSessionCreationPolicy Source # 
type Rep PlayerSessionCreationPolicy = D1 (MetaData "PlayerSessionCreationPolicy" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "AcceptAll" PrefixI False) U1) (C1 (MetaCons "DenyAll" PrefixI False) U1))

PlayerSessionStatus

data PlayerSessionStatus Source #

Instances

Bounded PlayerSessionStatus Source # 
Enum PlayerSessionStatus Source # 
Eq PlayerSessionStatus Source # 
Data PlayerSessionStatus Source # 

Methods

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

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

toConstr :: PlayerSessionStatus -> Constr #

dataTypeOf :: PlayerSessionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: PlayerSessionStatus -> () #

ToHeader PlayerSessionStatus Source # 
ToQuery PlayerSessionStatus Source # 
ToByteString PlayerSessionStatus Source # 
FromText PlayerSessionStatus Source # 
ToText PlayerSessionStatus Source # 
type Rep PlayerSessionStatus Source # 
type Rep PlayerSessionStatus = D1 (MetaData "PlayerSessionStatus" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) (C1 (MetaCons "PSSActive" PrefixI False) U1) (C1 (MetaCons "PSSCompleted" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PSSReserved" PrefixI False) U1) (C1 (MetaCons "PSSTimedout" PrefixI False) U1)))

ProtectionPolicy

data ProtectionPolicy Source #

Instances

Bounded ProtectionPolicy Source # 
Enum ProtectionPolicy Source # 
Eq ProtectionPolicy Source # 
Data ProtectionPolicy Source # 

Methods

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

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

toConstr :: ProtectionPolicy -> Constr #

dataTypeOf :: ProtectionPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ProtectionPolicy -> () #

ToHeader ProtectionPolicy Source # 
ToQuery ProtectionPolicy Source # 
ToByteString ProtectionPolicy Source # 
FromText ProtectionPolicy Source # 
ToText ProtectionPolicy Source # 
type Rep ProtectionPolicy Source # 
type Rep ProtectionPolicy = D1 (MetaData "ProtectionPolicy" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "FullProtection" PrefixI False) U1) (C1 (MetaCons "NoProtection" PrefixI False) U1))

RoutingStrategyType

data RoutingStrategyType Source #

Constructors

Simple 
Terminal 

Instances

Bounded RoutingStrategyType Source # 
Enum RoutingStrategyType Source # 
Eq RoutingStrategyType Source # 
Data RoutingStrategyType Source # 

Methods

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

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

toConstr :: RoutingStrategyType -> Constr #

dataTypeOf :: RoutingStrategyType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: RoutingStrategyType -> () #

ToHeader RoutingStrategyType Source # 
ToQuery RoutingStrategyType Source # 
ToByteString RoutingStrategyType Source # 
FromText RoutingStrategyType Source # 
ToText RoutingStrategyType Source # 
type Rep RoutingStrategyType Source # 
type Rep RoutingStrategyType = D1 (MetaData "RoutingStrategyType" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "Simple" PrefixI False) U1) (C1 (MetaCons "Terminal" PrefixI False) U1))

ScalingAdjustmentType

data ScalingAdjustmentType Source #

Instances

Bounded ScalingAdjustmentType Source # 
Enum ScalingAdjustmentType Source # 
Eq ScalingAdjustmentType Source # 
Data ScalingAdjustmentType Source # 

Methods

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

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

toConstr :: ScalingAdjustmentType -> Constr #

dataTypeOf :: ScalingAdjustmentType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ScalingAdjustmentType -> () #

ToHeader ScalingAdjustmentType Source # 
ToQuery ScalingAdjustmentType Source # 
ToByteString ScalingAdjustmentType Source # 
FromText ScalingAdjustmentType Source # 
ToText ScalingAdjustmentType Source # 
type Rep ScalingAdjustmentType Source # 
type Rep ScalingAdjustmentType = D1 (MetaData "ScalingAdjustmentType" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) (C1 (MetaCons "ChangeInCapacity" PrefixI False) U1) ((:+:) (C1 (MetaCons "ExactCapacity" PrefixI False) U1) (C1 (MetaCons "PercentChangeInCapacity" PrefixI False) U1)))

ScalingStatusType

data ScalingStatusType Source #

Instances

Bounded ScalingStatusType Source # 
Enum ScalingStatusType Source # 
Eq ScalingStatusType Source # 
Data ScalingStatusType Source # 

Methods

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

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

toConstr :: ScalingStatusType -> Constr #

dataTypeOf :: ScalingStatusType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ScalingStatusType -> () #

ToHeader ScalingStatusType Source # 
ToQuery ScalingStatusType Source # 
ToByteString ScalingStatusType Source # 
FromText ScalingStatusType Source # 
ToText ScalingStatusType Source # 
type Rep ScalingStatusType Source # 
type Rep ScalingStatusType = D1 (MetaData "ScalingStatusType" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) ((:+:) ((:+:) (C1 (MetaCons "Active" PrefixI False) U1) ((:+:) (C1 (MetaCons "DeleteRequested" PrefixI False) U1) (C1 (MetaCons "Deleted" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Deleting" PrefixI False) U1) (C1 (MetaCons "Error'" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UpdateRequested" PrefixI False) U1) (C1 (MetaCons "Updating" PrefixI False) U1))))

AWSCredentials

data AWSCredentials Source #

AWS access credentials required to upload game build files to Amazon GameLift. These credentials are generated with CreateBuild , and are valid for a limited time. If they expire before you upload your game build, get a new set by calling RequestUploadCredentials .

See: awsCredentials smart constructor.

Instances

Eq AWSCredentials Source # 
Data AWSCredentials Source # 

Methods

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

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

toConstr :: AWSCredentials -> Constr #

dataTypeOf :: AWSCredentials -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AWSCredentials Source # 
Show AWSCredentials Source # 
Generic AWSCredentials Source # 

Associated Types

type Rep AWSCredentials :: * -> * #

Hashable AWSCredentials Source # 
FromJSON AWSCredentials Source # 
NFData AWSCredentials Source # 

Methods

rnf :: AWSCredentials -> () #

type Rep AWSCredentials Source # 
type Rep AWSCredentials = D1 (MetaData "AWSCredentials" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "AWSCredentials'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_acSecretAccessKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_acSessionToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acAccessKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

awsCredentials :: AWSCredentials Source #

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

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

acSecretAccessKey :: Lens' AWSCredentials (Maybe Text) Source #

Secret key for an AWS account.

acSessionToken :: Lens' AWSCredentials (Maybe Text) Source #

Token specific to a build ID.

acAccessKeyId :: Lens' AWSCredentials (Maybe Text) Source #

Access key for an AWS account.

Alias

data Alias Source #

Properties describing a fleet alias.

See: alias smart constructor.

Instances

Eq Alias Source # 

Methods

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

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

Data Alias Source # 

Methods

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

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

toConstr :: Alias -> Constr #

dataTypeOf :: Alias -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Alias Source # 
Show Alias Source # 

Methods

showsPrec :: Int -> Alias -> ShowS #

show :: Alias -> String #

showList :: [Alias] -> ShowS #

Generic Alias Source # 

Associated Types

type Rep Alias :: * -> * #

Methods

from :: Alias -> Rep Alias x #

to :: Rep Alias x -> Alias #

Hashable Alias Source # 

Methods

hashWithSalt :: Int -> Alias -> Int #

hash :: Alias -> Int #

FromJSON Alias Source # 
NFData Alias Source # 

Methods

rnf :: Alias -> () #

type Rep Alias Source # 

alias :: Alias Source #

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

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

  • aCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • aLastUpdatedTime - Time stamp indicating when this data object was last modified. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • aAliasId - Unique identifier for a fleet alias.
  • aRoutingStrategy - Undocumented member.
  • aName - Descriptive label associated with an alias. Alias names do not need to be unique.
  • aDescription - Human-readable description of an alias.

aCreationTime :: Lens' Alias (Maybe UTCTime) Source #

Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

aLastUpdatedTime :: Lens' Alias (Maybe UTCTime) Source #

Time stamp indicating when this data object was last modified. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

aAliasId :: Lens' Alias (Maybe Text) Source #

Unique identifier for a fleet alias.

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

Descriptive label associated with an alias. Alias names do not need to be unique.

aDescription :: Lens' Alias (Maybe Text) Source #

Human-readable description of an alias.

Build

data Build Source #

Properties describing a game build.

See: build smart constructor.

Instances

Eq Build Source # 

Methods

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

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

Data Build Source # 

Methods

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

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

toConstr :: Build -> Constr #

dataTypeOf :: Build -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Build Source # 
Show Build Source # 

Methods

showsPrec :: Int -> Build -> ShowS #

show :: Build -> String #

showList :: [Build] -> ShowS #

Generic Build Source # 

Associated Types

type Rep Build :: * -> * #

Methods

from :: Build -> Rep Build x #

to :: Rep Build x -> Build #

Hashable Build Source # 

Methods

hashWithSalt :: Int -> Build -> Int #

hash :: Build -> Int #

FromJSON Build Source # 
NFData Build Source # 

Methods

rnf :: Build -> () #

type Rep Build Source # 

build :: Build Source #

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

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

  • bCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • bStatus - Current status of the build. Possible build statuses include the following: * INITIALIZED – A new build has been defined, but no files have been uploaded. You cannot create fleets for builds that are in this status. When a build is successfully created, the build status is set to this value. * READY – The game build has been successfully uploaded. You can now create new fleets for this build. * FAILED – The game build upload failed. You cannot create new fleets for this build.
  • bOperatingSystem - Operating system that the game server binaries are built to run on. This value determines the type of fleet resources that you can use for this build.
  • bBuildId - Unique identifier for a build.
  • bName - Descriptive label associated with a build. Build names do not need to be unique. It can be set using CreateBuild or UpdateBuild .
  • bVersion - Version associated with this build. Version strings do not need to be unique to a build. This value can be set using CreateBuild or UpdateBuild .
  • bSizeOnDisk - File size of the uploaded game build, expressed in bytes. When the build status is INITIALIZED , this value is 0.

bCreationTime :: Lens' Build (Maybe UTCTime) Source #

Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

bStatus :: Lens' Build (Maybe BuildStatus) Source #

Current status of the build. Possible build statuses include the following: * INITIALIZED – A new build has been defined, but no files have been uploaded. You cannot create fleets for builds that are in this status. When a build is successfully created, the build status is set to this value. * READY – The game build has been successfully uploaded. You can now create new fleets for this build. * FAILED – The game build upload failed. You cannot create new fleets for this build.

bOperatingSystem :: Lens' Build (Maybe OperatingSystem) Source #

Operating system that the game server binaries are built to run on. This value determines the type of fleet resources that you can use for this build.

bBuildId :: Lens' Build (Maybe Text) Source #

Unique identifier for a build.

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

Descriptive label associated with a build. Build names do not need to be unique. It can be set using CreateBuild or UpdateBuild .

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

Version associated with this build. Version strings do not need to be unique to a build. This value can be set using CreateBuild or UpdateBuild .

bSizeOnDisk :: Lens' Build (Maybe Natural) Source #

File size of the uploaded game build, expressed in bytes. When the build status is INITIALIZED , this value is 0.

EC2InstanceCounts

data EC2InstanceCounts Source #

Current status of fleet capacity. The number of active instances should match or be in the process of matching the number of desired instances. Pending and terminating counts are non-zero only if fleet capacity is adjusting to an UpdateFleetCapacity request, or if access to resources is temporarily affected.

See: ec2InstanceCounts smart constructor.

Instances

Eq EC2InstanceCounts Source # 
Data EC2InstanceCounts Source # 

Methods

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

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

toConstr :: EC2InstanceCounts -> Constr #

dataTypeOf :: EC2InstanceCounts -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EC2InstanceCounts -> () #

type Rep EC2InstanceCounts Source # 

ec2InstanceCounts :: EC2InstanceCounts Source #

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

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

  • eicIdLE - Number of active instances in the fleet that are not currently hosting a game session.
  • eicTERMINATING - Number of instances in the fleet that are no longer active but haven't yet been terminated.
  • eicPENDING - Number of instances in the fleet that are starting but not yet active.
  • eicMAXIMUM - Maximum value allowed for the fleet's instance count.
  • eicDESIRED - Ideal number of active instances in the fleet.
  • eicMINIMUM - Minimum value allowed for the fleet's instance count.
  • eicACTIVE - Actual number of active instances in the fleet.

eicIdLE :: Lens' EC2InstanceCounts (Maybe Natural) Source #

Number of active instances in the fleet that are not currently hosting a game session.

eicTERMINATING :: Lens' EC2InstanceCounts (Maybe Natural) Source #

Number of instances in the fleet that are no longer active but haven't yet been terminated.

eicPENDING :: Lens' EC2InstanceCounts (Maybe Natural) Source #

Number of instances in the fleet that are starting but not yet active.

eicMAXIMUM :: Lens' EC2InstanceCounts (Maybe Natural) Source #

Maximum value allowed for the fleet's instance count.

eicDESIRED :: Lens' EC2InstanceCounts (Maybe Natural) Source #

Ideal number of active instances in the fleet.

eicMINIMUM :: Lens' EC2InstanceCounts (Maybe Natural) Source #

Minimum value allowed for the fleet's instance count.

eicACTIVE :: Lens' EC2InstanceCounts (Maybe Natural) Source #

Actual number of active instances in the fleet.

EC2InstanceLimit

data EC2InstanceLimit Source #

Maximum number of instances allowed based on the Amazon Elastic Compute Cloud (Amazon EC2) instance type. Instance limits can be retrieved by calling DescribeEC2InstanceLimits .

See: ec2InstanceLimit smart constructor.

Instances

Eq EC2InstanceLimit Source # 
Data EC2InstanceLimit Source # 

Methods

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

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

toConstr :: EC2InstanceLimit -> Constr #

dataTypeOf :: EC2InstanceLimit -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EC2InstanceLimit -> () #

type Rep EC2InstanceLimit Source # 
type Rep EC2InstanceLimit = D1 (MetaData "EC2InstanceLimit" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "EC2InstanceLimit'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_eilEC2InstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EC2InstanceType))) ((:*:) (S1 (MetaSel (Just Symbol "_eilCurrentInstances") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_eilInstanceLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))

ec2InstanceLimit :: EC2InstanceLimit Source #

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

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

  • eilEC2InstanceType - Name of an EC2 instance type that is supported in Amazon GameLift. A fleet instance type determines the computing resources of each instance in the fleet, including CPU, memory, storage, and networking capacity. GameLift supports the following EC2 instance types. See Amazon EC2 Instance Types for detailed descriptions.
  • eilCurrentInstances - Number of instances of the specified type that are currently in use by this AWS account.
  • eilInstanceLimit - Number of instances allowed.

eilEC2InstanceType :: Lens' EC2InstanceLimit (Maybe EC2InstanceType) Source #

Name of an EC2 instance type that is supported in Amazon GameLift. A fleet instance type determines the computing resources of each instance in the fleet, including CPU, memory, storage, and networking capacity. GameLift supports the following EC2 instance types. See Amazon EC2 Instance Types for detailed descriptions.

eilCurrentInstances :: Lens' EC2InstanceLimit (Maybe Natural) Source #

Number of instances of the specified type that are currently in use by this AWS account.

eilInstanceLimit :: Lens' EC2InstanceLimit (Maybe Natural) Source #

Number of instances allowed.

Event

data Event Source #

Log entry describing an event involving Amazon GameLift resources (such as a fleet). In addition to tracking activity, event codes and messages can provide additional information for troubleshooting and debugging problems.

See: event smart constructor.

Instances

Eq Event Source # 

Methods

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

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

Data Event Source # 

Methods

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

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

toConstr :: Event -> Constr #

dataTypeOf :: Event -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Event Source # 
Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Hashable Event Source # 

Methods

hashWithSalt :: Int -> Event -> Int #

hash :: Event -> Int #

FromJSON Event Source # 
NFData Event Source # 

Methods

rnf :: Event -> () #

type Rep Event Source # 

event :: Event Source #

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

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

  • eResourceId - Unique identifier for the resource, such as a fleet ID.
  • eEventTime - Time stamp indicating when this event occurred. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • eMessage - Additional information related to the event.
  • eEventCode - Type of event being logged.
  • eEventId - Unique identifier for a fleet event.

eResourceId :: Lens' Event (Maybe Text) Source #

Unique identifier for the resource, such as a fleet ID.

eEventTime :: Lens' Event (Maybe UTCTime) Source #

Time stamp indicating when this event occurred. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

eMessage :: Lens' Event (Maybe Text) Source #

Additional information related to the event.

eEventCode :: Lens' Event (Maybe EventCode) Source #

Type of event being logged.

eEventId :: Lens' Event (Maybe Text) Source #

Unique identifier for a fleet event.

FleetAttributes

data FleetAttributes Source #

General properties describing a fleet.

See: fleetAttributes smart constructor.

Instances

Eq FleetAttributes Source # 
Data FleetAttributes Source # 

Methods

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

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

toConstr :: FleetAttributes -> Constr #

dataTypeOf :: FleetAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: FleetAttributes -> () #

type Rep FleetAttributes Source # 
type Rep FleetAttributes = D1 (MetaData "FleetAttributes" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "FleetAttributes'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) ((:*:) (S1 (MetaSel (Just Symbol "_faStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FleetStatus))) (S1 (MetaSel (Just Symbol "_faServerLaunchParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_faLogPaths") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_faOperatingSystem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OperatingSystem))) (S1 (MetaSel (Just Symbol "_faBuildId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faTerminationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) ((:*:) (S1 (MetaSel (Just Symbol "_faNewGameSessionProtectionPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProtectionPolicy))) (S1 (MetaSel (Just Symbol "_faName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faServerLaunchPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_faFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_faDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_faResourceCreationLimitPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResourceCreationLimitPolicy))))))))

fleetAttributes :: FleetAttributes Source #

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

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

  • faCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • faStatus - Current status of the fleet. Possible fleet statuses include the following: * NEW – A new fleet has been defined and desired instances is set to 1. * DOWNLOADINGVALIDATINGBUILDING/ACTIVATING – GameLift is setting up the new fleet, creating new instances with the game build and starting server processes. * ACTIVE – Hosts can now accept game sessions. * ERROR – An error occurred when downloading, validating, building, or activating the fleet. * DELETING – Hosts are responding to a delete fleet request. * TERMINATED – The fleet no longer exists.
  • faServerLaunchParameters - Game server launch parameters specified for fleets created prior to 2016-08-04 (or AWS SDK v. 0.12.16). Server launch parameters for fleets created after this date are specified in the fleet's RuntimeConfiguration .
  • faLogPaths - Location of default log files. When a server process is shut down, Amazon GameLift captures and stores any log files in this location. These logs are in addition to game session logs; see more on game session logs in the Amazon GameLift Developer Guide . If no default log path for a fleet is specified, GameLift will automatically upload logs that are stored on each instance at C:gamelogs (for Windows) or localgame/logs (for Linux). Use the GameLift console to access stored logs.
  • faOperatingSystem - Operating system of the fleet's computing resources. A fleet's operating system depends on the OS specified for the build that is deployed on this fleet.
  • faBuildId - Unique identifier for a build.
  • faTerminationTime - Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • faNewGameSessionProtectionPolicy - Type of game session protection to set for all new instances started in the fleet. * NoProtection – The game session can be terminated during a scale-down event. * FullProtection – If the game session is in an ACTIVE status, it cannot be terminated during a scale-down event.
  • faName - Descriptive label associated with a fleet. Fleet names do not need to be unique.
  • faServerLaunchPath - Path to a game server executable in the fleet's build, specified for fleets created prior to 2016-08-04 (or AWS SDK v. 0.12.16). Server launch paths for fleets created after this date are specified in the fleet's RuntimeConfiguration .
  • faFleetId - Unique identifier for a fleet.
  • faDescription - Human-readable description of the fleet.
  • faResourceCreationLimitPolicy - Fleet policy to limit the number of game sessions an individual player can create over a span of time.

faCreationTime :: Lens' FleetAttributes (Maybe UTCTime) Source #

Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

faStatus :: Lens' FleetAttributes (Maybe FleetStatus) Source #

Current status of the fleet. Possible fleet statuses include the following: * NEW – A new fleet has been defined and desired instances is set to 1. * DOWNLOADINGVALIDATINGBUILDING/ACTIVATING – GameLift is setting up the new fleet, creating new instances with the game build and starting server processes. * ACTIVE – Hosts can now accept game sessions. * ERROR – An error occurred when downloading, validating, building, or activating the fleet. * DELETING – Hosts are responding to a delete fleet request. * TERMINATED – The fleet no longer exists.

faServerLaunchParameters :: Lens' FleetAttributes (Maybe Text) Source #

Game server launch parameters specified for fleets created prior to 2016-08-04 (or AWS SDK v. 0.12.16). Server launch parameters for fleets created after this date are specified in the fleet's RuntimeConfiguration .

faLogPaths :: Lens' FleetAttributes [Text] Source #

Location of default log files. When a server process is shut down, Amazon GameLift captures and stores any log files in this location. These logs are in addition to game session logs; see more on game session logs in the Amazon GameLift Developer Guide . If no default log path for a fleet is specified, GameLift will automatically upload logs that are stored on each instance at C:gamelogs (for Windows) or localgame/logs (for Linux). Use the GameLift console to access stored logs.

faOperatingSystem :: Lens' FleetAttributes (Maybe OperatingSystem) Source #

Operating system of the fleet's computing resources. A fleet's operating system depends on the OS specified for the build that is deployed on this fleet.

faBuildId :: Lens' FleetAttributes (Maybe Text) Source #

Unique identifier for a build.

faTerminationTime :: Lens' FleetAttributes (Maybe UTCTime) Source #

Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

faNewGameSessionProtectionPolicy :: Lens' FleetAttributes (Maybe ProtectionPolicy) Source #

Type of game session protection to set for all new instances started in the fleet. * NoProtection – The game session can be terminated during a scale-down event. * FullProtection – If the game session is in an ACTIVE status, it cannot be terminated during a scale-down event.

faName :: Lens' FleetAttributes (Maybe Text) Source #

Descriptive label associated with a fleet. Fleet names do not need to be unique.

faServerLaunchPath :: Lens' FleetAttributes (Maybe Text) Source #

Path to a game server executable in the fleet's build, specified for fleets created prior to 2016-08-04 (or AWS SDK v. 0.12.16). Server launch paths for fleets created after this date are specified in the fleet's RuntimeConfiguration .

faFleetId :: Lens' FleetAttributes (Maybe Text) Source #

Unique identifier for a fleet.

faDescription :: Lens' FleetAttributes (Maybe Text) Source #

Human-readable description of the fleet.

faResourceCreationLimitPolicy :: Lens' FleetAttributes (Maybe ResourceCreationLimitPolicy) Source #

Fleet policy to limit the number of game sessions an individual player can create over a span of time.

FleetCapacity

data FleetCapacity Source #

Information about the fleet's capacity. Fleet capacity is measured in EC2 instances. By default, new fleets have a capacity of one instance, but can be updated as needed. The maximum number of instances for a fleet is determined by the fleet's instance type.

See: fleetCapacity smart constructor.

Instances

Eq FleetCapacity Source # 
Data FleetCapacity Source # 

Methods

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

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

toConstr :: FleetCapacity -> Constr #

dataTypeOf :: FleetCapacity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FleetCapacity Source # 
Show FleetCapacity Source # 
Generic FleetCapacity Source # 

Associated Types

type Rep FleetCapacity :: * -> * #

Hashable FleetCapacity Source # 
FromJSON FleetCapacity Source # 
NFData FleetCapacity Source # 

Methods

rnf :: FleetCapacity -> () #

type Rep FleetCapacity Source # 
type Rep FleetCapacity = D1 (MetaData "FleetCapacity" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "FleetCapacity'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fcInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EC2InstanceType))) ((:*:) (S1 (MetaSel (Just Symbol "_fcFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fcInstanceCounts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EC2InstanceCounts))))))

fleetCapacity :: FleetCapacity Source #

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

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

  • fcInstanceType - Name of an EC2 instance type that is supported in Amazon GameLift. A fleet instance type determines the computing resources of each instance in the fleet, including CPU, memory, storage, and networking capacity. GameLift supports the following EC2 instance types. See Amazon EC2 Instance Types for detailed descriptions.
  • fcFleetId - Unique identifier for a fleet.
  • fcInstanceCounts - Current status of fleet capacity.

fcInstanceType :: Lens' FleetCapacity (Maybe EC2InstanceType) Source #

Name of an EC2 instance type that is supported in Amazon GameLift. A fleet instance type determines the computing resources of each instance in the fleet, including CPU, memory, storage, and networking capacity. GameLift supports the following EC2 instance types. See Amazon EC2 Instance Types for detailed descriptions.

fcFleetId :: Lens' FleetCapacity (Maybe Text) Source #

Unique identifier for a fleet.

fcInstanceCounts :: Lens' FleetCapacity (Maybe EC2InstanceCounts) Source #

Current status of fleet capacity.

FleetUtilization

data FleetUtilization Source #

Current status of fleet utilization, including the number of game and player sessions being hosted.

See: fleetUtilization smart constructor.

Instances

Eq FleetUtilization Source # 
Data FleetUtilization Source # 

Methods

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

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

toConstr :: FleetUtilization -> Constr #

dataTypeOf :: FleetUtilization -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: FleetUtilization -> () #

type Rep FleetUtilization Source # 
type Rep FleetUtilization = D1 (MetaData "FleetUtilization" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "FleetUtilization'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fuActiveGameSessionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_fuMaximumPlayerSessionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)))) ((:*:) (S1 (MetaSel (Just Symbol "_fuCurrentPlayerSessionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) ((:*:) (S1 (MetaSel (Just Symbol "_fuFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fuActiveServerProcessCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)))))))

fleetUtilization :: FleetUtilization Source #

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

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

fuActiveGameSessionCount :: Lens' FleetUtilization (Maybe Natural) Source #

Number of active game sessions currently being hosted on all instances in the fleet.

fuMaximumPlayerSessionCount :: Lens' FleetUtilization (Maybe Natural) Source #

Maximum players allowed across all game sessions currently being hosted on all instances in the fleet.

fuCurrentPlayerSessionCount :: Lens' FleetUtilization (Maybe Natural) Source #

Number of active player sessions currently being hosted on all instances in the fleet.

fuFleetId :: Lens' FleetUtilization (Maybe Text) Source #

Unique identifier for a fleet.

fuActiveServerProcessCount :: Lens' FleetUtilization (Maybe Natural) Source #

Number of server processes in an ACTIVE status currently running across all instances in the fleet

GameProperty

data GameProperty Source #

Set of key-value pairs containing information a server process requires to set up a game session. This object allows you to pass in any set of data needed for your game. For more information, see the Amazon GameLift Developer Guide .

See: gameProperty smart constructor.

Instances

Eq GameProperty Source # 
Data GameProperty Source # 

Methods

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

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

toConstr :: GameProperty -> Constr #

dataTypeOf :: GameProperty -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GameProperty Source # 
Show GameProperty Source # 
Generic GameProperty Source # 

Associated Types

type Rep GameProperty :: * -> * #

Hashable GameProperty Source # 
ToJSON GameProperty Source # 
FromJSON GameProperty Source # 
NFData GameProperty Source # 

Methods

rnf :: GameProperty -> () #

type Rep GameProperty Source # 
type Rep GameProperty = D1 (MetaData "GameProperty" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "GameProperty'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gpKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_gpValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

gameProperty Source #

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

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

GameSession

data GameSession Source #

Properties describing a game session.

See: gameSession smart constructor.

Instances

Eq GameSession Source # 
Data GameSession Source # 

Methods

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

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

toConstr :: GameSession -> Constr #

dataTypeOf :: GameSession -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GameSession Source # 
Show GameSession Source # 
Generic GameSession Source # 

Associated Types

type Rep GameSession :: * -> * #

Hashable GameSession Source # 
FromJSON GameSession Source # 
NFData GameSession Source # 

Methods

rnf :: GameSession -> () #

type Rep GameSession Source # 
type Rep GameSession = D1 (MetaData "GameSession" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "GameSession'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gsCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) ((:*:) (S1 (MetaSel (Just Symbol "_gsStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GameSessionStatus))) (S1 (MetaSel (Just Symbol "_gsGameProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [GameProperty]))))) ((:*:) (S1 (MetaSel (Just Symbol "_gsIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_gsGameSessionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gsMaximumPlayerSessionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gsTerminationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) ((:*:) (S1 (MetaSel (Just Symbol "_gsPlayerSessionCreationPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PlayerSessionCreationPolicy))) (S1 (MetaSel (Just Symbol "_gsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gsCurrentPlayerSessionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_gsFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_gsCreatorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gsPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))))

gameSession :: GameSession Source #

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

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

  • gsCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • gsStatus - Current status of the game session. A game session must be in an ACTIVE status to have player sessions.
  • gsGameProperties - Set of custom properties for the game session.
  • gsIPAddress - IP address of the game session. To connect to a GameLift server process, an app needs both the IP address and port number.
  • gsGameSessionId - Unique identifier for a game session. Game session ID format is as follows: "arn:aws:gamelift:region::gamesessionfleet-IDstring". The value of string is either a custom ID string (if one was specified when the game session was created) an autogenerated string.
  • gsMaximumPlayerSessionCount - Maximum number of players allowed in the game session.
  • gsTerminationTime - Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • gsPlayerSessionCreationPolicy - Indicates whether or not the game session is accepting new players.
  • gsName - Descriptive label associated with a game session. Session names do not need to be unique.
  • gsCurrentPlayerSessionCount - Number of players currently in the game session.
  • gsFleetId - Unique identifier for a fleet.
  • gsCreatorId - Player ID of the person or entity that created the game session. This ID is used to enforce a resource protection policy (if one exists) that limits the number of concurrent active game sessions for a single player.
  • gsPort - Port number for the game session. To connect to a GameLift server process, an app needs both the IP address and port number.

gsCreationTime :: Lens' GameSession (Maybe UTCTime) Source #

Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

gsStatus :: Lens' GameSession (Maybe GameSessionStatus) Source #

Current status of the game session. A game session must be in an ACTIVE status to have player sessions.

gsGameProperties :: Lens' GameSession [GameProperty] Source #

Set of custom properties for the game session.

gsIPAddress :: Lens' GameSession (Maybe Text) Source #

IP address of the game session. To connect to a GameLift server process, an app needs both the IP address and port number.

gsGameSessionId :: Lens' GameSession (Maybe Text) Source #

Unique identifier for a game session. Game session ID format is as follows: "arn:aws:gamelift:region::gamesessionfleet-IDstring". The value of string is either a custom ID string (if one was specified when the game session was created) an autogenerated string.

gsMaximumPlayerSessionCount :: Lens' GameSession (Maybe Natural) Source #

Maximum number of players allowed in the game session.

gsTerminationTime :: Lens' GameSession (Maybe UTCTime) Source #

Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

gsPlayerSessionCreationPolicy :: Lens' GameSession (Maybe PlayerSessionCreationPolicy) Source #

Indicates whether or not the game session is accepting new players.

gsName :: Lens' GameSession (Maybe Text) Source #

Descriptive label associated with a game session. Session names do not need to be unique.

gsCurrentPlayerSessionCount :: Lens' GameSession (Maybe Natural) Source #

Number of players currently in the game session.

gsFleetId :: Lens' GameSession (Maybe Text) Source #

Unique identifier for a fleet.

gsCreatorId :: Lens' GameSession (Maybe Text) Source #

Player ID of the person or entity that created the game session. This ID is used to enforce a resource protection policy (if one exists) that limits the number of concurrent active game sessions for a single player.

gsPort :: Lens' GameSession (Maybe Natural) Source #

Port number for the game session. To connect to a GameLift server process, an app needs both the IP address and port number.

GameSessionDetail

data GameSessionDetail Source #

A game session's properties and the protection policy currently in force.

See: gameSessionDetail smart constructor.

Instances

Eq GameSessionDetail Source # 
Data GameSessionDetail Source # 

Methods

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

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

toConstr :: GameSessionDetail -> Constr #

dataTypeOf :: GameSessionDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GameSessionDetail -> () #

type Rep GameSessionDetail Source # 
type Rep GameSessionDetail = D1 (MetaData "GameSessionDetail" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "GameSessionDetail'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gsdGameSession") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GameSession))) (S1 (MetaSel (Just Symbol "_gsdProtectionPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProtectionPolicy)))))

gameSessionDetail :: GameSessionDetail Source #

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

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

  • gsdGameSession - Undocumented member.
  • gsdProtectionPolicy - Current status of protection for the game session. * NoProtection – The game session can be terminated during a scale-down event. * FullProtection – If the game session is in an ACTIVE status, it cannot be terminated during a scale-down event.

gsdProtectionPolicy :: Lens' GameSessionDetail (Maybe ProtectionPolicy) Source #

Current status of protection for the game session. * NoProtection – The game session can be terminated during a scale-down event. * FullProtection – If the game session is in an ACTIVE status, it cannot be terminated during a scale-down event.

IPPermission

data IPPermission Source #

A range of IP addresses and port settings that allow inbound traffic to connect to server processes on GameLift. Each game session hosted on a fleet is assigned a unique combination of IP address and port number, which must fall into the fleet's allowed ranges. This combination is included in the GameSession object.

See: ipPermission smart constructor.

Instances

Eq IPPermission Source # 
Data IPPermission Source # 

Methods

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

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

toConstr :: IPPermission -> Constr #

dataTypeOf :: IPPermission -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IPPermission Source # 
Show IPPermission Source # 
Generic IPPermission Source # 

Associated Types

type Rep IPPermission :: * -> * #

Hashable IPPermission Source # 
ToJSON IPPermission Source # 
FromJSON IPPermission Source # 
NFData IPPermission Source # 

Methods

rnf :: IPPermission -> () #

type Rep IPPermission Source # 
type Rep IPPermission = D1 (MetaData "IPPermission" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "IPPermission'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ipFromPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat)) (S1 (MetaSel (Just Symbol "_ipToPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat))) ((:*:) (S1 (MetaSel (Just Symbol "_ipIPRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_ipProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IPProtocol)))))

ipPermission Source #

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

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

  • ipFromPort - Starting value for a range of allowed port numbers.
  • ipToPort - Ending value for a range of allowed port numbers. Port numbers are end-inclusive. This value must be higher than FromPort .
  • ipIPRange - Range of allowed IP addresses. This value must be expressed in CIDR notation . Example: "000.000.000.000/[subnet mask] " or optionally the shortened version "0.0.0.0/[subnet mask] ".
  • ipProtocol - Network communication protocol used by the fleet.

ipFromPort :: Lens' IPPermission Natural Source #

Starting value for a range of allowed port numbers.

ipToPort :: Lens' IPPermission Natural Source #

Ending value for a range of allowed port numbers. Port numbers are end-inclusive. This value must be higher than FromPort .

ipIPRange :: Lens' IPPermission Text Source #

Range of allowed IP addresses. This value must be expressed in CIDR notation . Example: "000.000.000.000/[subnet mask] " or optionally the shortened version "0.0.0.0/[subnet mask] ".

ipProtocol :: Lens' IPPermission IPProtocol Source #

Network communication protocol used by the fleet.

Instance

data Instance Source #

Properties that describe an instance of a virtual computing resource that hosts one or more game servers. A fleet contains zero or more instances.

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 # 

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:

  • iCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • iInstanceId - Unique identifier for the instance.
  • iStatus - Current status of the instance. Possible statuses include the following: * PENDING – The instance is in the process of being created and launching server processes as defined in the fleet's runtime configuration. * ACTIVE – The instance has been successfully created and at least one server process has successfully launched and reported back to GameLift that it is ready to host a game session. The instance is now considered ready to host game sessions. * TERMINATING – The instance is in the process of shutting down. This may happen to reduce capacity during a scaling down event or to recycle resources in the event of a problem.
  • iIPAddress - IP address assigned to the instance.
  • iOperatingSystem - Operating system that is running on this instance.
  • iType - EC2 instance type that defines the computing resources of this instance.
  • iFleetId - Unique identifier for the fleet that the instance belongs to.

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

Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

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

Unique identifier for the instance.

iStatus :: Lens' Instance (Maybe InstanceStatus) Source #

Current status of the instance. Possible statuses include the following: * PENDING – The instance is in the process of being created and launching server processes as defined in the fleet's runtime configuration. * ACTIVE – The instance has been successfully created and at least one server process has successfully launched and reported back to GameLift that it is ready to host a game session. The instance is now considered ready to host game sessions. * TERMINATING – The instance is in the process of shutting down. This may happen to reduce capacity during a scaling down event or to recycle resources in the event of a problem.

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

IP address assigned to the instance.

iOperatingSystem :: Lens' Instance (Maybe OperatingSystem) Source #

Operating system that is running on this instance.

iType :: Lens' Instance (Maybe EC2InstanceType) Source #

EC2 instance type that defines the computing resources of this instance.

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

Unique identifier for the fleet that the instance belongs to.

InstanceAccess

data InstanceAccess Source #

Information required to remotely connect to a fleet instance. Access is requested by calling GetInstanceAccess .

See: instanceAccess smart constructor.

Instances

Eq InstanceAccess Source # 
Data InstanceAccess Source # 

Methods

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

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

toConstr :: InstanceAccess -> Constr #

dataTypeOf :: InstanceAccess -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InstanceAccess Source # 
Show InstanceAccess Source # 
Generic InstanceAccess Source # 

Associated Types

type Rep InstanceAccess :: * -> * #

Hashable InstanceAccess Source # 
FromJSON InstanceAccess Source # 
NFData InstanceAccess Source # 

Methods

rnf :: InstanceAccess -> () #

type Rep InstanceAccess Source # 
type Rep InstanceAccess = D1 (MetaData "InstanceAccess" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "InstanceAccess'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_iaInstanceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_iaIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_iaOperatingSystem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OperatingSystem))) ((:*:) (S1 (MetaSel (Just Symbol "_iaCredentials") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Sensitive InstanceCredentials)))) (S1 (MetaSel (Just Symbol "_iaFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

instanceAccess :: InstanceAccess Source #

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

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

  • iaInstanceId - Unique identifier for the instance being accessed.
  • iaIPAddress - IP address assigned to the instance.
  • iaOperatingSystem - Operating system that is running on the instance.
  • iaCredentials - Credentials required to access the instance.
  • iaFleetId - Unique identifier for the fleet containing the instance being accessed.

iaInstanceId :: Lens' InstanceAccess (Maybe Text) Source #

Unique identifier for the instance being accessed.

iaIPAddress :: Lens' InstanceAccess (Maybe Text) Source #

IP address assigned to the instance.

iaOperatingSystem :: Lens' InstanceAccess (Maybe OperatingSystem) Source #

Operating system that is running on the instance.

iaCredentials :: Lens' InstanceAccess (Maybe InstanceCredentials) Source #

Credentials required to access the instance.

iaFleetId :: Lens' InstanceAccess (Maybe Text) Source #

Unique identifier for the fleet containing the instance being accessed.

InstanceCredentials

data InstanceCredentials Source #

Set of credentials required to remotely access a fleet instance. Access credentials are requested by calling GetInstanceAccess and returned in an InstanceAccess object.

See: instanceCredentials smart constructor.

Instances

Eq InstanceCredentials Source # 
Data InstanceCredentials Source # 

Methods

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

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

toConstr :: InstanceCredentials -> Constr #

dataTypeOf :: InstanceCredentials -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceCredentials -> () #

type Rep InstanceCredentials Source # 
type Rep InstanceCredentials = D1 (MetaData "InstanceCredentials" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "InstanceCredentials'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_icUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_icSecret") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

instanceCredentials :: InstanceCredentials Source #

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

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

  • icUserName - User login string.
  • icSecret - Secret string. For Windows instances, the secret is a password. For Linux instances, it is a private key.

icSecret :: Lens' InstanceCredentials (Maybe Text) Source #

Secret string. For Windows instances, the secret is a password. For Linux instances, it is a private key.

PlayerSession

data PlayerSession Source #

Properties describing a player session.

See: playerSession smart constructor.

Instances

Eq PlayerSession Source # 
Data PlayerSession Source # 

Methods

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

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

toConstr :: PlayerSession -> Constr #

dataTypeOf :: PlayerSession -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PlayerSession Source # 
Show PlayerSession Source # 
Generic PlayerSession Source # 

Associated Types

type Rep PlayerSession :: * -> * #

Hashable PlayerSession Source # 
FromJSON PlayerSession Source # 
NFData PlayerSession Source # 

Methods

rnf :: PlayerSession -> () #

type Rep PlayerSession Source # 

playerSession :: PlayerSession Source #

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

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

  • psCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • psStatus - Current status of the player session. Possible player session statuses include the following: * RESERVED – The player session request has been received, but the player has not yet connected to the server process andor been validated. * ACTIVE – The player has been validated by the server process and is currently connected. * COMPLETED – The player connection has been dropped. * TIMEDOUT – A player session request was received, but the player did not connect andor was not validated within the time-out limit (60 seconds).
  • psIPAddress - Game session IP address. All player sessions reference the game session location.
  • psGameSessionId - Unique identifier for the game session that the player session is connected to.
  • psTerminationTime - Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").
  • psPlayerSessionId - Unique identifier for a player session.
  • psFleetId - Unique identifier for a fleet.
  • psPlayerId - Unique identifier for a player.
  • psPort - Port number for the game session. To connect to a GameLift server process, an app needs both the IP address and port number.

psCreationTime :: Lens' PlayerSession (Maybe UTCTime) Source #

Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

psStatus :: Lens' PlayerSession (Maybe PlayerSessionStatus) Source #

Current status of the player session. Possible player session statuses include the following: * RESERVED – The player session request has been received, but the player has not yet connected to the server process andor been validated. * ACTIVE – The player has been validated by the server process and is currently connected. * COMPLETED – The player connection has been dropped. * TIMEDOUT – A player session request was received, but the player did not connect andor was not validated within the time-out limit (60 seconds).

psIPAddress :: Lens' PlayerSession (Maybe Text) Source #

Game session IP address. All player sessions reference the game session location.

psGameSessionId :: Lens' PlayerSession (Maybe Text) Source #

Unique identifier for the game session that the player session is connected to.

psTerminationTime :: Lens' PlayerSession (Maybe UTCTime) Source #

Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (ex: "1469498468.057").

psPlayerSessionId :: Lens' PlayerSession (Maybe Text) Source #

Unique identifier for a player session.

psFleetId :: Lens' PlayerSession (Maybe Text) Source #

Unique identifier for a fleet.

psPlayerId :: Lens' PlayerSession (Maybe Text) Source #

Unique identifier for a player.

psPort :: Lens' PlayerSession (Maybe Natural) Source #

Port number for the game session. To connect to a GameLift server process, an app needs both the IP address and port number.

ResourceCreationLimitPolicy

data ResourceCreationLimitPolicy Source #

Policy that limits the number of game sessions a player can create on the same fleet. This optional policy gives game owners control over how players can consume available game server resources. A resource creation policy makes the following statement: "An individual player can create a maximum number of new game sessions within a specified time period".

The policy is evaluated when a player tries to create a new game session. For example, with a policy of 10 new game sessions and a time period of 60 minutes, on receiving a CreateGameSession request, GameLift checks that the player (identified by CreatorId ) has created fewer than 10 game sessions in the past 60 minutes.

See: resourceCreationLimitPolicy smart constructor.

Instances

Eq ResourceCreationLimitPolicy Source # 
Data ResourceCreationLimitPolicy Source # 

Methods

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

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

toConstr :: ResourceCreationLimitPolicy -> Constr #

dataTypeOf :: ResourceCreationLimitPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ResourceCreationLimitPolicy Source # 
Show ResourceCreationLimitPolicy Source # 
Generic ResourceCreationLimitPolicy Source # 
Hashable ResourceCreationLimitPolicy Source # 
ToJSON ResourceCreationLimitPolicy Source # 
FromJSON ResourceCreationLimitPolicy Source # 
NFData ResourceCreationLimitPolicy Source # 
type Rep ResourceCreationLimitPolicy Source # 
type Rep ResourceCreationLimitPolicy = D1 (MetaData "ResourceCreationLimitPolicy" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "ResourceCreationLimitPolicy'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rclpNewGameSessionsPerCreator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_rclpPolicyPeriodInMinutes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)))))

resourceCreationLimitPolicy :: ResourceCreationLimitPolicy Source #

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

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

rclpNewGameSessionsPerCreator :: Lens' ResourceCreationLimitPolicy (Maybe Natural) Source #

Maximum number of game sessions that an individual can create during the policy period.

rclpPolicyPeriodInMinutes :: Lens' ResourceCreationLimitPolicy (Maybe Natural) Source #

Time span used in evaluating the resource creation limit policy.

RoutingStrategy

data RoutingStrategy Source #

Routing configuration for a fleet alias.

See: routingStrategy smart constructor.

Instances

Eq RoutingStrategy Source # 
Data RoutingStrategy Source # 

Methods

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

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

toConstr :: RoutingStrategy -> Constr #

dataTypeOf :: RoutingStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: RoutingStrategy -> () #

type Rep RoutingStrategy Source # 
type Rep RoutingStrategy = D1 (MetaData "RoutingStrategy" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "RoutingStrategy'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rsType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RoutingStrategyType))) ((:*:) (S1 (MetaSel (Just Symbol "_rsMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rsFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

routingStrategy :: RoutingStrategy Source #

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

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

  • rsType - Type of routing strategy. Possible routing types include the following: * SIMPLE – The alias resolves to one specific fleet. Use this type when routing to active fleets. * TERMINAL – The alias does not resolve to a fleet but instead can be used to display a message to the user. A terminal alias throws a TerminalRoutingStrategyException with the RoutingStrategy message embedded.
  • rsMessage - Message text to be used with a terminal routing strategy.
  • rsFleetId - Unique identifier for a fleet.

rsType :: Lens' RoutingStrategy (Maybe RoutingStrategyType) Source #

Type of routing strategy. Possible routing types include the following: * SIMPLE – The alias resolves to one specific fleet. Use this type when routing to active fleets. * TERMINAL – The alias does not resolve to a fleet but instead can be used to display a message to the user. A terminal alias throws a TerminalRoutingStrategyException with the RoutingStrategy message embedded.

rsMessage :: Lens' RoutingStrategy (Maybe Text) Source #

Message text to be used with a terminal routing strategy.

rsFleetId :: Lens' RoutingStrategy (Maybe Text) Source #

Unique identifier for a fleet.

RuntimeConfiguration

data RuntimeConfiguration Source #

Collection of server process configurations that describe what processes should be run on each instance in a fleet. An instance can launch and maintain multiple server processes based on the runtime configuration; it regularly checks for an updated runtime configuration and starts new server processes to match the latest version.

The key purpose of a runtime configuration with multiple server process configurations is to be able to run more than one kind of game server in a single fleet. You can include configurations for more than one server executable in order to run two or more different programs to run on the same instance. This option might be useful, for example, to run more than one version of your game server on the same fleet. Another option is to specify configurations for the same server executable but with different launch parameters.

A GameLift instance is limited to 50 processes running simultaneously. To calculate the total number of processes specified in a runtime configuration, add the values of the ConcurrentExecutions parameter for each ServerProcess object in the runtime configuration.

See: runtimeConfiguration smart constructor.

Instances

Eq RuntimeConfiguration Source # 
Data RuntimeConfiguration Source # 

Methods

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

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

toConstr :: RuntimeConfiguration -> Constr #

dataTypeOf :: RuntimeConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: RuntimeConfiguration -> () #

type Rep RuntimeConfiguration Source # 
type Rep RuntimeConfiguration = D1 (MetaData "RuntimeConfiguration" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" True) (C1 (MetaCons "RuntimeConfiguration'" PrefixI True) (S1 (MetaSel (Just Symbol "_rcServerProcesses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (List1 ServerProcess)))))

runtimeConfiguration :: RuntimeConfiguration Source #

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

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

  • rcServerProcesses - Collection of server process configurations describing what server processes to run on each instance in a fleet

rcServerProcesses :: Lens' RuntimeConfiguration (Maybe (NonEmpty ServerProcess)) Source #

Collection of server process configurations describing what server processes to run on each instance in a fleet

S3Location

data S3Location Source #

Location in Amazon Simple Storage Service (Amazon S3) where a build's files are stored. This location is assigned in response to a CreateBuild call, and is always in the same region as the service used to create the build. For more details see the Amazon S3 documentation .

See: s3Location smart constructor.

Instances

Eq S3Location Source # 
Data S3Location Source # 

Methods

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

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

toConstr :: S3Location -> Constr #

dataTypeOf :: S3Location -> DataType #

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

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

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

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

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

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

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

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

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

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

Read S3Location Source # 
Show S3Location Source # 
Generic S3Location Source # 

Associated Types

type Rep S3Location :: * -> * #

Hashable S3Location Source # 
ToJSON S3Location Source # 
FromJSON S3Location Source # 
NFData S3Location Source # 

Methods

rnf :: S3Location -> () #

type Rep S3Location Source # 
type Rep S3Location = D1 (MetaData "S3Location" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "S3Location'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_slBucket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_slKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_slRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

s3Location :: S3Location Source #

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

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

  • slBucket - Amazon S3 bucket identifier.
  • slKey - Amazon S3 bucket key.
  • slRoleARN - Amazon resource number for the cross-account access role that allows GameLift access to the S3 bucket.

slBucket :: Lens' S3Location (Maybe Text) Source #

Amazon S3 bucket identifier.

slKey :: Lens' S3Location (Maybe Text) Source #

Amazon S3 bucket key.

slRoleARN :: Lens' S3Location (Maybe Text) Source #

Amazon resource number for the cross-account access role that allows GameLift access to the S3 bucket.

ScalingPolicy

data ScalingPolicy Source #

Rule that controls how a fleet is scaled. Scaling policies are uniquely identified by the combination of name and fleet ID.

See: scalingPolicy smart constructor.

Instances

Eq ScalingPolicy Source # 
Data ScalingPolicy Source # 

Methods

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

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

toConstr :: ScalingPolicy -> Constr #

dataTypeOf :: ScalingPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ScalingPolicy Source # 
Show ScalingPolicy Source # 
Generic ScalingPolicy Source # 

Associated Types

type Rep ScalingPolicy :: * -> * #

Hashable ScalingPolicy Source # 
FromJSON ScalingPolicy Source # 
NFData ScalingPolicy Source # 

Methods

rnf :: ScalingPolicy -> () #

type Rep ScalingPolicy Source # 

scalingPolicy :: ScalingPolicy Source #

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

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

  • spStatus - Current status of the scaling policy. The scaling policy is only in force when in an ACTIVE status. * ACTIVE – The scaling policy is currently in force. * UPDATE_REQUESTED – A request to update the scaling policy has been received. * UPDATING – A change is being made to the scaling policy. * DELETE_REQUESTED – A request to delete the scaling policy has been received. * DELETING – The scaling policy is being deleted. * DELETED – The scaling policy has been deleted. * ERROR – An error occurred in creating the policy. It should be removed and recreated.
  • spScalingAdjustmentType - Type of adjustment to make to a fleet's instance count (see FleetCapacity ): * ChangeInCapacity – add (or subtract) the scaling adjustment value from the current instance count. Positive values scale up while negative values scale down. * ExactCapacity – set the instance count to the scaling adjustment value. * PercentChangeInCapacity – increase or reduce the current instance count by the scaling adjustment, read as a percentage. Positive values scale up while negative values scale down.
  • spEvaluationPeriods - Length of time (in minutes) the metric must be at or beyond the threshold before a scaling event is triggered.
  • spMetricName - Name of the GameLift-defined metric that is used to trigger an adjustment. * ActivatingGameSessions – number of game sessions in the process of being created (game session status = ACTIVATING ). * ActiveGameSessions – number of game sessions currently running (game session status = ACTIVE ). * CurrentPlayerSessions – number of active or reserved player sessions (player session status = ACTIVE or RESERVED ). * AvailablePlayerSessions – number of player session slots currently available in active game sessions across the fleet, calculated by subtracting a game session's current player session count from its maximum player session count. This number does include game sessions that are not currently accepting players (game session PlayerSessionCreationPolicy = DENY_ALL ). * ActiveInstances – number of instances currently running a game session. * IdleInstances – number of instances not currently running a game session.
  • spComparisonOperator - Comparison operator to use when measuring a metric against the threshold value.
  • spName - Descriptive label associated with a scaling policy. Policy names do not need to be unique.
  • spThreshold - Metric value used to trigger a scaling event.
  • spScalingAdjustment - Amount of adjustment to make, based on the scaling adjustment type.
  • spFleetId - Unique identity for the fleet associated with this scaling policy.

spStatus :: Lens' ScalingPolicy (Maybe ScalingStatusType) Source #

Current status of the scaling policy. The scaling policy is only in force when in an ACTIVE status. * ACTIVE – The scaling policy is currently in force. * UPDATE_REQUESTED – A request to update the scaling policy has been received. * UPDATING – A change is being made to the scaling policy. * DELETE_REQUESTED – A request to delete the scaling policy has been received. * DELETING – The scaling policy is being deleted. * DELETED – The scaling policy has been deleted. * ERROR – An error occurred in creating the policy. It should be removed and recreated.

spScalingAdjustmentType :: Lens' ScalingPolicy (Maybe ScalingAdjustmentType) Source #

Type of adjustment to make to a fleet's instance count (see FleetCapacity ): * ChangeInCapacity – add (or subtract) the scaling adjustment value from the current instance count. Positive values scale up while negative values scale down. * ExactCapacity – set the instance count to the scaling adjustment value. * PercentChangeInCapacity – increase or reduce the current instance count by the scaling adjustment, read as a percentage. Positive values scale up while negative values scale down.

spEvaluationPeriods :: Lens' ScalingPolicy (Maybe Natural) Source #

Length of time (in minutes) the metric must be at or beyond the threshold before a scaling event is triggered.

spMetricName :: Lens' ScalingPolicy (Maybe MetricName) Source #

Name of the GameLift-defined metric that is used to trigger an adjustment. * ActivatingGameSessions – number of game sessions in the process of being created (game session status = ACTIVATING ). * ActiveGameSessions – number of game sessions currently running (game session status = ACTIVE ). * CurrentPlayerSessions – number of active or reserved player sessions (player session status = ACTIVE or RESERVED ). * AvailablePlayerSessions – number of player session slots currently available in active game sessions across the fleet, calculated by subtracting a game session's current player session count from its maximum player session count. This number does include game sessions that are not currently accepting players (game session PlayerSessionCreationPolicy = DENY_ALL ). * ActiveInstances – number of instances currently running a game session. * IdleInstances – number of instances not currently running a game session.

spComparisonOperator :: Lens' ScalingPolicy (Maybe ComparisonOperatorType) Source #

Comparison operator to use when measuring a metric against the threshold value.

spName :: Lens' ScalingPolicy (Maybe Text) Source #

Descriptive label associated with a scaling policy. Policy names do not need to be unique.

spThreshold :: Lens' ScalingPolicy (Maybe Double) Source #

Metric value used to trigger a scaling event.

spScalingAdjustment :: Lens' ScalingPolicy (Maybe Int) Source #

Amount of adjustment to make, based on the scaling adjustment type.

spFleetId :: Lens' ScalingPolicy (Maybe Text) Source #

Unique identity for the fleet associated with this scaling policy.

ServerProcess

data ServerProcess Source #

A set of instructions for launching server processes on each instance in a fleet. Each instruction set identifies the location of the server executable, optional launch parameters, and the number of server processes with this configuration to maintain concurrently on the instance. Server process configurations make up a fleet's RuntimeConfiguration .

See: serverProcess smart constructor.

Instances

Eq ServerProcess Source # 
Data ServerProcess Source # 

Methods

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

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

toConstr :: ServerProcess -> Constr #

dataTypeOf :: ServerProcess -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServerProcess Source # 
Show ServerProcess Source # 
Generic ServerProcess Source # 

Associated Types

type Rep ServerProcess :: * -> * #

Hashable ServerProcess Source # 
ToJSON ServerProcess Source # 
FromJSON ServerProcess Source # 
NFData ServerProcess Source # 

Methods

rnf :: ServerProcess -> () #

type Rep ServerProcess Source # 
type Rep ServerProcess = D1 (MetaData "ServerProcess" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.4.5-2krZbzEaIqtLV8ATX8AZ52" False) (C1 (MetaCons "ServerProcess'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_spParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_spLaunchPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_spConcurrentExecutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat)))))

serverProcess Source #

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

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

  • spParameters - Optional list of parameters to pass to the server executable on launch.
  • spLaunchPath - Location of the server executable in a game build. All game builds are installed on instances at the root : for Windows instances C:game , and for Linux instances localgame . A Windows game build with an executable file located at MyGamelatestserver.exe must have a launch path of "C:gameMyGamelatestserver.exe ". A Linux game build with an executable file located at MyGamelatestserver.exe must have a launch path of "localgameMyGamelatest/server.exe ".
  • spConcurrentExecutions - Number of server processes using this configuration to run concurrently on an instance.

spParameters :: Lens' ServerProcess (Maybe Text) Source #

Optional list of parameters to pass to the server executable on launch.

spLaunchPath :: Lens' ServerProcess Text Source #

Location of the server executable in a game build. All game builds are installed on instances at the root : for Windows instances C:game , and for Linux instances localgame . A Windows game build with an executable file located at MyGamelatestserver.exe must have a launch path of "C:gameMyGamelatestserver.exe ". A Linux game build with an executable file located at MyGamelatestserver.exe must have a launch path of "localgameMyGamelatest/server.exe ".

spConcurrentExecutions :: Lens' ServerProcess Natural Source #

Number of server processes using this configuration to run concurrently on an instance.