amazonka-gamelift-1.5.0: Amazon GameLift SDK.

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

Network.AWS.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.

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

The requested operation is not supported in the region specified.

_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.

AcceptanceType

data AcceptanceType Source #

Constructors

Accept 
Reject 

Instances

Bounded AcceptanceType Source # 
Enum AcceptanceType Source # 
Eq AcceptanceType Source # 
Data AcceptanceType Source # 

Methods

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

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

toConstr :: AcceptanceType -> Constr #

dataTypeOf :: AcceptanceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AcceptanceType Source # 
Read AcceptanceType Source # 
Show AcceptanceType Source # 
Generic AcceptanceType Source # 

Associated Types

type Rep AcceptanceType :: * -> * #

Hashable AcceptanceType Source # 
ToJSON AcceptanceType Source # 
NFData AcceptanceType Source # 

Methods

rnf :: AcceptanceType -> () #

ToQuery AcceptanceType Source # 
ToHeader AcceptanceType Source # 
ToByteString AcceptanceType Source # 
FromText AcceptanceType Source # 
ToText AcceptanceType Source # 
type Rep AcceptanceType Source # 
type Rep AcceptanceType = D1 (MetaData "AcceptanceType" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) ((:+:) (C1 (MetaCons "Accept" PrefixI False) U1) (C1 (MetaCons "Reject" PrefixI False) U1))

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 # 
FromJSON BuildStatus Source # 
ToJSON BuildStatus Source # 
NFData BuildStatus Source # 

Methods

rnf :: BuildStatus -> () #

ToQuery BuildStatus Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON ComparisonOperatorType Source # 
ToJSON ComparisonOperatorType Source # 
NFData ComparisonOperatorType Source # 

Methods

rnf :: ComparisonOperatorType -> () #

ToQuery ComparisonOperatorType Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON EC2InstanceType Source # 
ToJSON EC2InstanceType Source # 
NFData EC2InstanceType Source # 

Methods

rnf :: EC2InstanceType -> () #

ToQuery EC2InstanceType Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 "R4_16XLarge" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "R4_2XLarge" PrefixI False) U1) (C1 (MetaCons "R4_4XLarge" PrefixI False) U1)) ((:+:) (C1 (MetaCons "R4_8XLarge" PrefixI False) U1) (C1 (MetaCons "R4_Large" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "R4_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 -> () #

ToQuery EventCode Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 "FleetCreationExtractingBuild" PrefixI False) U1) (C1 (MetaCons "FleetCreationRunningInstaller" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FleetCreationValidatingRuntimeConfig" 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 "FleetVPCPeeringDeleted" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FleetVPCPeeringFailed" PrefixI False) U1) (C1 (MetaCons "FleetVPCPeeringSucceeded" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "FleetValidationExecutableRuntimeFailure" PrefixI False) U1) (C1 (MetaCons "FleetValidationLaunchPathNotFound" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FleetValidationTimedOut" PrefixI False) U1) (C1 (MetaCons "GameSessionActivationTimeout" 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 -> () #

ToQuery FleetStatus Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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)))))

GameSessionPlacementState

data GameSessionPlacementState Source #

Instances

Bounded GameSessionPlacementState Source # 
Enum GameSessionPlacementState Source # 
Eq GameSessionPlacementState Source # 
Data GameSessionPlacementState Source # 

Methods

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

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

toConstr :: GameSessionPlacementState -> Constr #

dataTypeOf :: GameSessionPlacementState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GameSessionPlacementState Source # 
Read GameSessionPlacementState Source # 
Show GameSessionPlacementState Source # 
Generic GameSessionPlacementState Source # 
Hashable GameSessionPlacementState Source # 
FromJSON GameSessionPlacementState Source # 
NFData GameSessionPlacementState Source # 
ToQuery GameSessionPlacementState Source # 
ToHeader GameSessionPlacementState Source # 
ToByteString GameSessionPlacementState Source # 
FromText GameSessionPlacementState Source # 
ToText GameSessionPlacementState Source # 
type Rep GameSessionPlacementState Source # 
type Rep GameSessionPlacementState = D1 (MetaData "GameSessionPlacementState" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) ((:+:) ((:+:) (C1 (MetaCons "Cancelled" PrefixI False) U1) (C1 (MetaCons "Fulfilled" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Pending" PrefixI False) U1) (C1 (MetaCons "TimedOut" 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 -> () #

ToQuery GameSessionStatus Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON IPProtocol Source # 
ToJSON IPProtocol Source # 
NFData IPProtocol Source # 

Methods

rnf :: IPProtocol -> () #

ToQuery IPProtocol Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 -> () #

ToQuery InstanceStatus Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" False) ((:+:) (C1 (MetaCons "ISActive" PrefixI False) U1) ((:+:) (C1 (MetaCons "ISPending" PrefixI False) U1) (C1 (MetaCons "ISTerminating" PrefixI False) U1)))

MatchmakingConfigurationStatus

data MatchmakingConfigurationStatus Source #

Instances

Bounded MatchmakingConfigurationStatus Source # 
Enum MatchmakingConfigurationStatus Source # 
Eq MatchmakingConfigurationStatus Source # 
Data MatchmakingConfigurationStatus Source # 

Methods

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

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

toConstr :: MatchmakingConfigurationStatus -> Constr #

dataTypeOf :: MatchmakingConfigurationStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MatchmakingConfigurationStatus Source # 
Read MatchmakingConfigurationStatus Source # 
Show MatchmakingConfigurationStatus Source # 
Generic MatchmakingConfigurationStatus Source # 
Hashable MatchmakingConfigurationStatus Source # 
FromJSON MatchmakingConfigurationStatus Source # 
NFData MatchmakingConfigurationStatus Source # 
ToQuery MatchmakingConfigurationStatus Source # 
ToHeader MatchmakingConfigurationStatus Source # 
ToByteString MatchmakingConfigurationStatus Source # 
FromText MatchmakingConfigurationStatus Source # 
ToText MatchmakingConfigurationStatus Source # 
type Rep MatchmakingConfigurationStatus Source # 
type Rep MatchmakingConfigurationStatus = D1 (MetaData "MatchmakingConfigurationStatus" "Network.AWS.GameLift.Types.Sum" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MCSCancelled" PrefixI False) U1) (C1 (MetaCons "MCSCompleted" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MCSFailed" PrefixI False) U1) (C1 (MetaCons "MCSPlacing" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "MCSQueued" PrefixI False) U1) (C1 (MetaCons "MCSRequiresAcceptance" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MCSSearching" PrefixI False) U1) (C1 (MetaCons "MCSTimedOut" 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 # 
FromJSON MetricName Source # 
ToJSON MetricName Source # 
NFData MetricName Source # 

Methods

rnf :: MetricName -> () #

ToQuery MetricName Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ActivatingGameSessions" PrefixI False) U1) (C1 (MetaCons "ActiveGameSessions" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ActiveInstances" PrefixI False) U1) ((:+:) (C1 (MetaCons "AvailableGameSessions" PrefixI False) U1) (C1 (MetaCons "AvailablePlayerSessions" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "CurrentPlayerSessions" PrefixI False) U1) ((:+:) (C1 (MetaCons "IdleInstances" PrefixI False) U1) (C1 (MetaCons "PercentAvailableGameSessions" PrefixI False) U1))) ((:+:) (C1 (MetaCons "PercentIdleInstances" PrefixI False) U1) ((:+:) (C1 (MetaCons "QueueDepth" PrefixI False) U1) (C1 (MetaCons "WaitTime" 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 # 
FromJSON OperatingSystem Source # 
ToJSON OperatingSystem Source # 
NFData OperatingSystem Source # 

Methods

rnf :: OperatingSystem -> () #

ToQuery OperatingSystem Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON PlayerSessionCreationPolicy Source # 
ToJSON PlayerSessionCreationPolicy Source # 
NFData PlayerSessionCreationPolicy Source # 
ToQuery PlayerSessionCreationPolicy Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 -> () #

ToQuery PlayerSessionStatus Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON ProtectionPolicy Source # 
ToJSON ProtectionPolicy Source # 
NFData ProtectionPolicy Source # 

Methods

rnf :: ProtectionPolicy -> () #

ToQuery ProtectionPolicy Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON RoutingStrategyType Source # 
ToJSON RoutingStrategyType Source # 
NFData RoutingStrategyType Source # 

Methods

rnf :: RoutingStrategyType -> () #

ToQuery RoutingStrategyType Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON ScalingAdjustmentType Source # 
ToJSON ScalingAdjustmentType Source # 
NFData ScalingAdjustmentType Source # 

Methods

rnf :: ScalingAdjustmentType -> () #

ToQuery ScalingAdjustmentType Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 # 
FromJSON ScalingStatusType Source # 
ToJSON ScalingStatusType Source # 
NFData ScalingStatusType Source # 

Methods

rnf :: ScalingStatusType -> () #

ToQuery ScalingStatusType Source # 
ToHeader 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 #

Temporary access credentials used for uploading game build files to Amazon GameLift. They 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 #

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.5.0-LWFsf2alHztGD91U7ab8u0" 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 - Temporary secret key allowing access to the Amazon GameLift S3 account.
  • acSessionToken - Token used to associate a specific build ID with the files uploaded using these credentials.
  • acAccessKeyId - Temporary key allowing access to the Amazon GameLift S3 account.

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

Temporary secret key allowing access to the Amazon GameLift S3 account.

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

Token used to associate a specific build ID with the files uploaded using these credentials.

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

Temporary key allowing access to the Amazon GameLift S3 account.

Alias

data Alias Source #

Properties describing a fleet alias.

Alias-related operations include:

  • CreateAlias
  • ListAliases
  • DescribeAlias
  • UpdateAlias
  • DeleteAlias
  • ResolveAlias

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 (for example "1469498468.057").
  • aLastUpdatedTime - Time stamp indicating when this data object was last modified. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • aAliasId - Unique identifier for an alias; alias IDs are unique within a region.
  • aRoutingStrategy - Alias configuration for the alias, including routing type and settings.
  • aName - Descriptive label that is associated with an alias. Alias names do not need to be unique.
  • aAliasARN - Unique identifier for an alias; alias ARNs are unique across all regions.
  • 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 (for example "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 (for example "1469498468.057").

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

Unique identifier for an alias; alias IDs are unique within a region.

aRoutingStrategy :: Lens' Alias (Maybe RoutingStrategy) Source #

Alias configuration for the alias, including routing type and settings.

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

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

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

Unique identifier for an alias; alias ARNs are unique across all regions.

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

Human-readable description of an alias.

AttributeValue

data AttributeValue Source #

Values for use in Player attribute type:value pairs. This object lets you specify an attribute value using any of the valid data types: string, number, string array or data map. Each AttributeValue object can use only one of the available properties.

See: attributeValue smart constructor.

Instances

Eq AttributeValue Source # 
Data AttributeValue Source # 

Methods

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

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

toConstr :: AttributeValue -> Constr #

dataTypeOf :: AttributeValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AttributeValue Source # 
Show AttributeValue Source # 
Generic AttributeValue Source # 

Associated Types

type Rep AttributeValue :: * -> * #

Hashable AttributeValue Source # 
FromJSON AttributeValue Source # 
ToJSON AttributeValue Source # 
NFData AttributeValue Source # 

Methods

rnf :: AttributeValue -> () #

type Rep AttributeValue Source # 
type Rep AttributeValue = D1 (MetaData "AttributeValue" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "AttributeValue'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avSL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_avSDM") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_avN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))) (S1 (MetaSel (Just Symbol "_avS") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

attributeValue :: AttributeValue Source #

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

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

  • avSL - For a list of up to 10 strings. Maximum length for each string is 100 characters. Duplicate values are not recognized; all occurrences of the repeated value after the first of a repeated value are ignored.
  • avSDM - For a map of up to 10 type:value pairs. Maximum length for each string value is 100 characters.
  • avN - For number values, expressed as double.
  • avS - For single string values. Maximum string length is 100 characters.

avSL :: Lens' AttributeValue [Text] Source #

For a list of up to 10 strings. Maximum length for each string is 100 characters. Duplicate values are not recognized; all occurrences of the repeated value after the first of a repeated value are ignored.

avSDM :: Lens' AttributeValue (HashMap Text Double) Source #

For a map of up to 10 type:value pairs. Maximum length for each string value is 100 characters.

avN :: Lens' AttributeValue (Maybe Double) Source #

For number values, expressed as double.

avS :: Lens' AttributeValue (Maybe Text) Source #

For single string values. Maximum string length is 100 characters.

Build

data Build Source #

Properties describing a game build.

Build-related operations include:

  • CreateBuild
  • ListBuilds
  • DescribeBuild
  • UpdateBuild
  • DeleteBuild

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 (for example "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 that is associated with a build. Build names do not need to be unique. It can be set using CreateBuild or UpdateBuild .
  • bVersion - Version that is associated with this build. Version strings do not need to be unique. 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 (for example "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 that is 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 that is associated with this build. Version strings do not need to be unique. 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.

DesiredPlayerSession

data DesiredPlayerSession Source #

Player information for use when creating player sessions using a game session placement request with StartGameSessionPlacement .

See: desiredPlayerSession smart constructor.

Instances

Eq DesiredPlayerSession Source # 
Data DesiredPlayerSession Source # 

Methods

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

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

toConstr :: DesiredPlayerSession -> Constr #

dataTypeOf :: DesiredPlayerSession -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: DesiredPlayerSession -> () #

type Rep DesiredPlayerSession Source # 
type Rep DesiredPlayerSession = D1 (MetaData "DesiredPlayerSession" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "DesiredPlayerSession'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dpsPlayerData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dpsPlayerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

desiredPlayerSession :: DesiredPlayerSession Source #

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

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

  • dpsPlayerData - Developer-defined information related to a player. Amazon GameLift does not use this data, so it can be formatted as needed for use in the game.
  • dpsPlayerId - Unique identifier for a player to associate with the player session.

dpsPlayerData :: Lens' DesiredPlayerSession (Maybe Text) Source #

Developer-defined information related to a player. Amazon GameLift does not use this data, so it can be formatted as needed for use in the game.

dpsPlayerId :: Lens' DesiredPlayerSession (Maybe Text) Source #

Unique identifier for a player to associate with the player session.

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.

Fleet-related operations include:

  • CreateFleet
  • ListFleets
  • Describe fleets:
  • DescribeFleetAttributes
  • DescribeFleetPortSettings
  • DescribeFleetUtilization
  • DescribeRuntimeConfiguration
  • DescribeFleetEvents
  • Update fleets:
  • UpdateFleetAttributes
  • UpdateFleetCapacity
  • UpdateFleetPortSettings
  • UpdateRuntimeConfiguration
  • Manage fleet capacity:
  • DescribeFleetCapacity
  • UpdateFleetCapacity
  • PutScalingPolicy (automatic scaling)
  • DescribeScalingPolicies (automatic scaling)
  • DeleteScalingPolicy (automatic scaling)
  • DescribeEC2InstanceLimits
  • DeleteFleet

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.5.0-LWFsf2alHztGD91U7ab8u0" 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. Amazon 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. Amazon 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 that involves 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 an event resource, such as a fleet ID.
  • ePreSignedLogURL - Location of stored logs with additional detail that is related to the event. This is useful for debugging issues. The URL is valid for 15 minutes. You can also access fleet creation logs through the Amazon GameLift console.
  • eEventTime - Time stamp indicating when this event occurred. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • eMessage - Additional information related to the event.
  • eEventCode - Type of event being logged. The following events are currently in use: General events: * GENERIC_EVENT -- An unspecified event has occurred. Fleet creation events: * FLEET_CREATED -- A fleet record was successfully created with a status of NEW . Event messaging includes the fleet ID. * FLEET_STATE_DOWNLOADING -- Fleet status changed from NEW to DOWNLOADING . The compressed build has started downloading to a fleet instance for installation. * FLEET_BINARY_DOWNLOAD_FAILED -- The build failed to download to the fleet instance. * FLEET_CREATION_EXTRACTING_BUILD – The game server build was successfully downloaded to an instance, and the build files are now being extracted from the uploaded build and saved to an instance. Failure at this stage prevents a fleet from moving to ACTIVE status. Logs for this stage display a list of the files that are extracted and saved on the instance. Access the logs by using the URL in PreSignedLogUrl . * FLEET_CREATION_RUNNING_INSTALLER – The game server build files were successfully extracted, and the Amazon GameLift is now running the build's install script (if one is included). Failure in this stage prevents a fleet from moving to ACTIVE status. Logs for this stage list the installation steps and whether or not the install completed successfully. Access the logs by using the URL in PreSignedLogUrl . * FLEET_CREATION_VALIDATING_RUNTIME_CONFIG -- The build process was successful, and the Amazon GameLift is now verifying that the game server launch paths, which are specified in the fleet's run-time configuration, exist. If any listed launch path exists, Amazon GameLift tries to launch a game server process and waits for the process to report ready. Failures in this stage prevent a fleet from moving to ACTIVE status. Logs for this stage list the launch paths in the run-time configuration and indicate whether each is found. Access the logs by using the URL in PreSignedLogUrl . * FLEET_STATE_VALIDATING -- Fleet status changed from DOWNLOADING to VALIDATING . * FLEET_VALIDATION_LAUNCH_PATH_NOT_FOUND -- Validation of the run-time configuration failed because the executable specified in a launch path does not exist on the instance. * FLEET_STATE_BUILDING -- Fleet status changed from VALIDATING to BUILDING . * FLEET_VALIDATION_EXECUTABLE_RUNTIME_FAILURE -- Validation of the run-time configuration failed because the executable specified in a launch path failed to run on the fleet instance. * FLEET_STATE_ACTIVATING -- Fleet status changed from BUILDING to ACTIVATING . * FLEET_ACTIVATION_FAILED - The fleet failed to successfully complete one of the steps in the fleet activation process. This event code indicates that the game build was successfully downloaded to a fleet instance, built, and validated, but was not able to start a server process. A possible reason for failure is that the game server is not reporting "process ready" to the Amazon GameLift service. * FLEET_STATE_ACTIVE -- The fleet's status changed from ACTIVATING to ACTIVE . The fleet is now ready to host game sessions. VPC peering events: * FLEET_VPC_PEERING_SUCCEEDED -- A VPC peering connection has been established between the VPC for an Amazon GameLift fleet and a VPC in your AWS account. * FLEET_VPC_PEERING_FAILED -- A requested VPC peering connection has failed. Event details and status information (see DescribeVpcPeeringConnections ) provide additional detail. A common reason for peering failure is that the two VPCs have overlapping CIDR blocks of IPv4 addresses. To resolve this, change the CIDR block for the VPC in your AWS account. For more information on VPC peering failures, see http://docs.aws.amazon.com/AmazonVPC/latest/PeeringGuide/invalid-peering-configurations.html * FLEET_VPC_PEERING_DELETED -- A VPC peering connection has been successfully deleted. Other fleet events: * FLEET_SCALING_EVENT -- A change was made to the fleet's capacity settings (desired instances, minimum/maximum scaling limits). Event messaging includes the new capacity settings. * FLEET_NEW_GAME_SESSION_PROTECTION_POLICY_UPDATED -- A change was made to the fleet's game session protection policy setting. Event messaging includes both the old and new policy setting. * FLEET_DELETED -- A request to delete a fleet was initiated.
  • eEventId - Unique identifier for a fleet event.

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

Unique identifier for an event resource, such as a fleet ID.

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

Location of stored logs with additional detail that is related to the event. This is useful for debugging issues. The URL is valid for 15 minutes. You can also access fleet creation logs through the Amazon GameLift console.

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

Time stamp indicating when this event occurred. Format is a number expressed in Unix time as milliseconds (for example "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. The following events are currently in use: General events: * GENERIC_EVENT -- An unspecified event has occurred. Fleet creation events: * FLEET_CREATED -- A fleet record was successfully created with a status of NEW . Event messaging includes the fleet ID. * FLEET_STATE_DOWNLOADING -- Fleet status changed from NEW to DOWNLOADING . The compressed build has started downloading to a fleet instance for installation. * FLEET_BINARY_DOWNLOAD_FAILED -- The build failed to download to the fleet instance. * FLEET_CREATION_EXTRACTING_BUILD – The game server build was successfully downloaded to an instance, and the build files are now being extracted from the uploaded build and saved to an instance. Failure at this stage prevents a fleet from moving to ACTIVE status. Logs for this stage display a list of the files that are extracted and saved on the instance. Access the logs by using the URL in PreSignedLogUrl . * FLEET_CREATION_RUNNING_INSTALLER – The game server build files were successfully extracted, and the Amazon GameLift is now running the build's install script (if one is included). Failure in this stage prevents a fleet from moving to ACTIVE status. Logs for this stage list the installation steps and whether or not the install completed successfully. Access the logs by using the URL in PreSignedLogUrl . * FLEET_CREATION_VALIDATING_RUNTIME_CONFIG -- The build process was successful, and the Amazon GameLift is now verifying that the game server launch paths, which are specified in the fleet's run-time configuration, exist. If any listed launch path exists, Amazon GameLift tries to launch a game server process and waits for the process to report ready. Failures in this stage prevent a fleet from moving to ACTIVE status. Logs for this stage list the launch paths in the run-time configuration and indicate whether each is found. Access the logs by using the URL in PreSignedLogUrl . * FLEET_STATE_VALIDATING -- Fleet status changed from DOWNLOADING to VALIDATING . * FLEET_VALIDATION_LAUNCH_PATH_NOT_FOUND -- Validation of the run-time configuration failed because the executable specified in a launch path does not exist on the instance. * FLEET_STATE_BUILDING -- Fleet status changed from VALIDATING to BUILDING . * FLEET_VALIDATION_EXECUTABLE_RUNTIME_FAILURE -- Validation of the run-time configuration failed because the executable specified in a launch path failed to run on the fleet instance. * FLEET_STATE_ACTIVATING -- Fleet status changed from BUILDING to ACTIVATING . * FLEET_ACTIVATION_FAILED - The fleet failed to successfully complete one of the steps in the fleet activation process. This event code indicates that the game build was successfully downloaded to a fleet instance, built, and validated, but was not able to start a server process. A possible reason for failure is that the game server is not reporting "process ready" to the Amazon GameLift service. * FLEET_STATE_ACTIVE -- The fleet's status changed from ACTIVATING to ACTIVE . The fleet is now ready to host game sessions. VPC peering events: * FLEET_VPC_PEERING_SUCCEEDED -- A VPC peering connection has been established between the VPC for an Amazon GameLift fleet and a VPC in your AWS account. * FLEET_VPC_PEERING_FAILED -- A requested VPC peering connection has failed. Event details and status information (see DescribeVpcPeeringConnections ) provide additional detail. A common reason for peering failure is that the two VPCs have overlapping CIDR blocks of IPv4 addresses. To resolve this, change the CIDR block for the VPC in your AWS account. For more information on VPC peering failures, see http://docs.aws.amazon.com/AmazonVPC/latest/PeeringGuide/invalid-peering-configurations.html * FLEET_VPC_PEERING_DELETED -- A VPC peering connection has been successfully deleted. Other fleet events: * FLEET_SCALING_EVENT -- A change was made to the fleet's capacity settings (desired instances, minimum/maximum scaling limits). Event messaging includes the new capacity settings. * FLEET_NEW_GAME_SESSION_PROTECTION_POLICY_UPDATED -- A change was made to the fleet's game session protection policy setting. Event messaging includes both the old and new policy setting. * FLEET_DELETED -- A request to delete a fleet was initiated.

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

Unique identifier for a fleet event.

FleetAttributes

data FleetAttributes Source #

General properties describing a fleet.

Fleet-related operations include:

  • CreateFleet
  • ListFleets
  • Describe fleets:
  • DescribeFleetAttributes
  • DescribeFleetPortSettings
  • DescribeFleetUtilization
  • DescribeRuntimeConfiguration
  • DescribeFleetEvents
  • Update fleets:
  • UpdateFleetAttributes
  • UpdateFleetCapacity
  • UpdateFleetPortSettings
  • UpdateRuntimeConfiguration
  • Manage fleet capacity:
  • DescribeFleetCapacity
  • UpdateFleetCapacity
  • PutScalingPolicy (automatic scaling)
  • DescribeScalingPolicies (automatic scaling)
  • DeleteScalingPolicy (automatic scaling)
  • DescribeEC2InstanceLimits
  • DeleteFleet

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.5.0-LWFsf2alHztGD91U7ab8u0" 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 "_faFleetARN") 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 "_faMetricGroups") 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 (for example "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 -- Amazon 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 before 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, Amazon GameLift automatically uploads logs that are stored on each instance at C:gamelogs (for Windows) or localgame/logs (for Linux). Use the Amazon 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.
  • faFleetARN - Identifier for a fleet that is unique across all regions.
  • faTerminationTime - Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (for example "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 that is 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 before 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 .
  • faMetricGroups - Names of metric groups that this fleet is included in. In Amazon CloudWatch, you can view metrics for an individual fleet or aggregated metrics for fleets that are in a fleet metric group. A fleet can be included in only one metric group at a time.
  • 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 (for example "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 -- Amazon 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 before 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, Amazon GameLift automatically uploads logs that are stored on each instance at C:gamelogs (for Windows) or localgame/logs (for Linux). Use the Amazon 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.

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

Identifier for a fleet that is unique across all regions.

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 (for example "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 that is 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 before 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 .

faMetricGroups :: Lens' FleetAttributes [Text] Source #

Names of metric groups that this fleet is included in. In Amazon CloudWatch, you can view metrics for an individual fleet or aggregated metrics for fleets that are in a fleet metric group. A fleet can be included in only one metric group at a time.

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.

Fleet-related operations include:

  • CreateFleet
  • ListFleets
  • Describe fleets:
  • DescribeFleetAttributes
  • DescribeFleetPortSettings
  • DescribeFleetUtilization
  • DescribeRuntimeConfiguration
  • DescribeFleetEvents
  • Update fleets:
  • UpdateFleetAttributes
  • UpdateFleetCapacity
  • UpdateFleetPortSettings
  • UpdateRuntimeConfiguration
  • Manage fleet capacity:
  • DescribeFleetCapacity
  • UpdateFleetCapacity
  • PutScalingPolicy (automatic scaling)
  • DescribeScalingPolicies (automatic scaling)
  • DeleteScalingPolicy (automatic scaling)
  • DescribeEC2InstanceLimits
  • DeleteFleet

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.5.0-LWFsf2alHztGD91U7ab8u0" 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. Amazon 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. Amazon 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.

Fleet-related operations include:

  • CreateFleet
  • ListFleets
  • Describe fleets:
  • DescribeFleetAttributes
  • DescribeFleetPortSettings
  • DescribeFleetUtilization
  • DescribeRuntimeConfiguration
  • DescribeFleetEvents
  • Update fleets:
  • UpdateFleetAttributes
  • UpdateFleetCapacity
  • UpdateFleetPortSettings
  • UpdateRuntimeConfiguration
  • Manage fleet capacity:
  • DescribeFleetCapacity
  • UpdateFleetCapacity
  • PutScalingPolicy (automatic scaling)
  • DescribeScalingPolicies (automatic scaling)
  • DeleteScalingPolicy (automatic scaling)
  • DescribeEC2InstanceLimits
  • DeleteFleet

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.5.0-LWFsf2alHztGD91U7ab8u0" 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 that contain information about a game session. When included in a game session request, these properties communicate details to be used when setting up the new game session, such as to specify a game mode, level, or map. Game properties are passed to the game server process when initiating a new game session; the server process uses the properties as appropriate. 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 # 
FromJSON GameProperty Source # 
ToJSON 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.5.0-LWFsf2alHztGD91U7ab8u0" 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:

  • gpKey - Game property identifier.
  • gpValue - Game property value.

gpKey :: Lens' GameProperty Text Source #

Game property identifier.

gpValue :: Lens' GameProperty Text Source #

Game property value.

GameSession

data GameSession Source #

Properties describing a game session.

A game session in ACTIVE status can host players. When a game session ends, its status is set to TERMINATED .

Once the session ends, the game session object is retained for 30 days. This means you can reuse idempotency token values after this time. Game session logs are retained for 14 days.

Game-session-related operations include:

  • CreateGameSession
  • DescribeGameSessions
  • DescribeGameSessionDetails
  • SearchGameSessions
  • UpdateGameSession
  • GetGameSessionLogUrl
  • Game session placements
  • StartGameSessionPlacement
  • DescribeGameSessionPlacement
  • StopGameSessionPlacement

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.5.0-LWFsf2alHztGD91U7ab8u0" 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 "_gsGameSessionData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (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 (for example "1469498468.057").
  • gsStatus - Current status of the game session. A game session must have an ACTIVE status to have player sessions.
  • gsGameProperties - Set of developer-defined properties for a game session, formatted as a set of type:value pairs. These properties are included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).
  • gsIPAddress - IP address of the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number.
  • gsGameSessionId - Unique identifier for the game session. A game session ARN has the following format: arn:aws:gamelift:region::gamesessionIDID string or idempotency token .
  • gsMaximumPlayerSessionCount - Maximum number of players that can be connected simultaneously to the game session.
  • gsTerminationTime - Time stamp indicating when this data object was terminated. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • gsPlayerSessionCreationPolicy - Indicates whether or not the game session is accepting new players.
  • gsName - Descriptive label that is associated with a game session. Session names do not need to be unique.
  • gsCurrentPlayerSessionCount - Number of players currently in the game session.
  • gsGameSessionData - Set of developer-defined game session properties, formatted as a single string value. This data is included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).
  • gsFleetId - Unique identifier for a fleet that the game session is running on.
  • gsCreatorId - Unique identifier for a player. This ID is used to enforce a resource protection policy (if one exists), that limits the number of game sessions a player can create.
  • gsPort - Port number for the game session. To connect to a Amazon GameLift game server, 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 (for example "1469498468.057").

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

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

gsGameProperties :: Lens' GameSession [GameProperty] Source #

Set of developer-defined properties for a game session, formatted as a set of type:value pairs. These properties are included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).

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

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

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

Unique identifier for the game session. A game session ARN has the following format: arn:aws:gamelift:region::gamesessionIDID string or idempotency token .

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

Maximum number of players that can be connected simultaneously to 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 (for example "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 that is 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.

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

Set of developer-defined game session properties, formatted as a single string value. This data is included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).

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

Unique identifier for a fleet that the game session is running on.

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

Unique identifier for a player. This ID is used to enforce a resource protection policy (if one exists), that limits the number of game sessions a player can create.

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

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

GameSessionConnectionInfo

data GameSessionConnectionInfo Source #

Connection information for the new game session that is created with matchmaking. (with StartMatchmaking ). Once a match is set, the FlexMatch engine places the match and creates a new game session for it. This information, including the game session endpoint and player sessions for each player in the original matchmaking request, is added to the MatchmakingTicket , which can be retrieved by calling DescribeMatchmaking .

See: gameSessionConnectionInfo smart constructor.

Instances

Eq GameSessionConnectionInfo Source # 
Data GameSessionConnectionInfo Source # 

Methods

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

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

toConstr :: GameSessionConnectionInfo -> Constr #

dataTypeOf :: GameSessionConnectionInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GameSessionConnectionInfo Source # 
Show GameSessionConnectionInfo Source # 
Generic GameSessionConnectionInfo Source # 
Hashable GameSessionConnectionInfo Source # 
FromJSON GameSessionConnectionInfo Source # 
NFData GameSessionConnectionInfo Source # 
type Rep GameSessionConnectionInfo Source # 
type Rep GameSessionConnectionInfo = D1 (MetaData "GameSessionConnectionInfo" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "GameSessionConnectionInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gsciMatchedPlayerSessions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MatchedPlayerSession]))) (S1 (MetaSel (Just Symbol "_gsciIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_gsciGameSessionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gsciPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))

gameSessionConnectionInfo :: GameSessionConnectionInfo Source #

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

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

  • gsciMatchedPlayerSessions - Collection of player session IDs, one for each player ID that was included in the original matchmaking request.
  • gsciIPAddress - IP address of the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number.
  • gsciGameSessionARN - Amazon Resource Name (ARN ) that is assigned to a game session and uniquely identifies it.
  • gsciPort - Port number for the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number.

gsciMatchedPlayerSessions :: Lens' GameSessionConnectionInfo [MatchedPlayerSession] Source #

Collection of player session IDs, one for each player ID that was included in the original matchmaking request.

gsciIPAddress :: Lens' GameSessionConnectionInfo (Maybe Text) Source #

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

gsciGameSessionARN :: Lens' GameSessionConnectionInfo (Maybe Text) Source #

Amazon Resource Name (ARN ) that is assigned to a game session and uniquely identifies it.

gsciPort :: Lens' GameSessionConnectionInfo (Maybe Natural) Source #

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

GameSessionDetail

data GameSessionDetail Source #

A game session's properties plus 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 - Object that describes a game session.
  • 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.

gsdGameSession :: Lens' GameSessionDetail (Maybe GameSession) Source #

Object that describes a game session.

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.

GameSessionPlacement

data GameSessionPlacement Source #

Object that describes a StartGameSessionPlacement request. This object includes the full details of the original request plus the current status and start/end time stamps.

Game session placement-related operations include:

  • StartGameSessionPlacement
  • DescribeGameSessionPlacement
  • StopGameSessionPlacement

See: gameSessionPlacement smart constructor.

Instances

Eq GameSessionPlacement Source # 
Data GameSessionPlacement Source # 

Methods

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

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

toConstr :: GameSessionPlacement -> Constr #

dataTypeOf :: GameSessionPlacement -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GameSessionPlacement -> () #

type Rep GameSessionPlacement Source # 
type Rep GameSessionPlacement = D1 (MetaData "GameSessionPlacement" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "GameSessionPlacement'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gspStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GameSessionPlacementState))) (S1 (MetaSel (Just Symbol "_gspPlacementId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_gspGameProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [GameProperty]))) (S1 (MetaSel (Just Symbol "_gspIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gspGameSessionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gspStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))) ((:*:) (S1 (MetaSel (Just Symbol "_gspGameSessionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gspGameSessionRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gspMaximumPlayerSessionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_gspEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))) ((:*:) (S1 (MetaSel (Just Symbol "_gspGameSessionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gspPlayerLatencies") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlayerLatency]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gspGameSessionData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gspGameSessionQueueName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_gspPlacedPlayerSessions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlacedPlayerSession]))) (S1 (MetaSel (Just Symbol "_gspPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))))

gameSessionPlacement :: GameSessionPlacement Source #

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

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

  • gspStatus - Current status of the game session placement request. * PENDING -- The placement request is currently in the queue waiting to be processed. * FULFILLED -- A new game session and player sessions (if requested) have been successfully created. Values for GameSessionArn and GameSessionRegion are available. * CANCELLED -- The placement request was canceled with a call to StopGameSessionPlacement . * TIMED_OUT -- A new game session was not successfully created before the time limit expired. You can resubmit the placement request as needed.
  • gspPlacementId - Unique identifier for a game session placement.
  • gspGameProperties - Set of developer-defined properties for a game session, formatted as a set of type:value pairs. These properties are included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).
  • gspIPAddress - IP address of the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number. This value is set once the new game session is placed (placement status is FULFILLED ).
  • gspGameSessionName - Descriptive label that is associated with a game session. Session names do not need to be unique.
  • gspStartTime - Time stamp indicating when this request was placed in the queue. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • gspGameSessionId - Unique identifier for the game session. This value is set once the new game session is placed (placement status is FULFILLED ).
  • gspGameSessionRegion - Name of the region where the game session created by this placement request is running. This value is set once the new game session is placed (placement status is FULFILLED ).
  • gspMaximumPlayerSessionCount - Maximum number of players that can be connected simultaneously to the game session.
  • gspEndTime - Time stamp indicating when this request was completed, canceled, or timed out.
  • gspGameSessionARN - Identifier for the game session created by this placement request. This value is set once the new game session is placed (placement status is FULFILLED ). This identifier is unique across all regions. You can use this value as a GameSessionId value as needed.
  • gspPlayerLatencies - Set of values, expressed in milliseconds, indicating the amount of latency that a player experiences when connected to AWS regions.
  • gspGameSessionData - Set of developer-defined game session properties, formatted as a single string value. This data is included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).
  • gspGameSessionQueueName - Descriptive label that is associated with game session queue. Queue names must be unique within each region.
  • gspPlacedPlayerSessions - Collection of information on player sessions created in response to the game session placement request. These player sessions are created only once a new game session is successfully placed (placement status is FULFILLED ). This information includes the player ID (as provided in the placement request) and the corresponding player session ID. Retrieve full player sessions by calling DescribePlayerSessions with the player session ID.
  • gspPort - Port number for the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number. This value is set once the new game session is placed (placement status is FULFILLED ).

gspStatus :: Lens' GameSessionPlacement (Maybe GameSessionPlacementState) Source #

Current status of the game session placement request. * PENDING -- The placement request is currently in the queue waiting to be processed. * FULFILLED -- A new game session and player sessions (if requested) have been successfully created. Values for GameSessionArn and GameSessionRegion are available. * CANCELLED -- The placement request was canceled with a call to StopGameSessionPlacement . * TIMED_OUT -- A new game session was not successfully created before the time limit expired. You can resubmit the placement request as needed.

gspPlacementId :: Lens' GameSessionPlacement (Maybe Text) Source #

Unique identifier for a game session placement.

gspGameProperties :: Lens' GameSessionPlacement [GameProperty] Source #

Set of developer-defined properties for a game session, formatted as a set of type:value pairs. These properties are included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).

gspIPAddress :: Lens' GameSessionPlacement (Maybe Text) Source #

IP address of the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number. This value is set once the new game session is placed (placement status is FULFILLED ).

gspGameSessionName :: Lens' GameSessionPlacement (Maybe Text) Source #

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

gspStartTime :: Lens' GameSessionPlacement (Maybe UTCTime) Source #

Time stamp indicating when this request was placed in the queue. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").

gspGameSessionId :: Lens' GameSessionPlacement (Maybe Text) Source #

Unique identifier for the game session. This value is set once the new game session is placed (placement status is FULFILLED ).

gspGameSessionRegion :: Lens' GameSessionPlacement (Maybe Text) Source #

Name of the region where the game session created by this placement request is running. This value is set once the new game session is placed (placement status is FULFILLED ).

gspMaximumPlayerSessionCount :: Lens' GameSessionPlacement (Maybe Natural) Source #

Maximum number of players that can be connected simultaneously to the game session.

gspEndTime :: Lens' GameSessionPlacement (Maybe UTCTime) Source #

Time stamp indicating when this request was completed, canceled, or timed out.

gspGameSessionARN :: Lens' GameSessionPlacement (Maybe Text) Source #

Identifier for the game session created by this placement request. This value is set once the new game session is placed (placement status is FULFILLED ). This identifier is unique across all regions. You can use this value as a GameSessionId value as needed.

gspPlayerLatencies :: Lens' GameSessionPlacement [PlayerLatency] Source #

Set of values, expressed in milliseconds, indicating the amount of latency that a player experiences when connected to AWS regions.

gspGameSessionData :: Lens' GameSessionPlacement (Maybe Text) Source #

Set of developer-defined game session properties, formatted as a single string value. This data is included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ).

gspGameSessionQueueName :: Lens' GameSessionPlacement (Maybe Text) Source #

Descriptive label that is associated with game session queue. Queue names must be unique within each region.

gspPlacedPlayerSessions :: Lens' GameSessionPlacement [PlacedPlayerSession] Source #

Collection of information on player sessions created in response to the game session placement request. These player sessions are created only once a new game session is successfully placed (placement status is FULFILLED ). This information includes the player ID (as provided in the placement request) and the corresponding player session ID. Retrieve full player sessions by calling DescribePlayerSessions with the player session ID.

gspPort :: Lens' GameSessionPlacement (Maybe Natural) Source #

Port number for the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number. This value is set once the new game session is placed (placement status is FULFILLED ).

GameSessionQueue

data GameSessionQueue Source #

Configuration of a queue that is used to process game session placement requests. The queue configuration identifies several game features:

  • The destinations where a new game session can potentially be hosted. Amazon GameLift tries these destinations in an order based on either the queue's default order or player latency information, if provided in a placement request. With latency information, Amazon GameLift can place game sessions where the majority of players are reporting the lowest possible latency.
  • The length of time that placement requests can wait in the queue before timing out.
  • A set of optional latency policies that protect individual players from high latencies, preventing game sessions from being placed where any individual player is reporting latency higher than a policy's maximum.

Queue-related operations include:

  • CreateGameSessionQueue
  • DescribeGameSessionQueues
  • UpdateGameSessionQueue
  • DeleteGameSessionQueue

See: gameSessionQueue smart constructor.

Instances

Eq GameSessionQueue Source # 
Data GameSessionQueue Source # 

Methods

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

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

toConstr :: GameSessionQueue -> Constr #

dataTypeOf :: GameSessionQueue -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GameSessionQueue -> () #

type Rep GameSessionQueue Source # 
type Rep GameSessionQueue = D1 (MetaData "GameSessionQueue" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "GameSessionQueue'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gsqGameSessionQueueARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gsqPlayerLatencyPolicies") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlayerLatencyPolicy])))) ((:*:) (S1 (MetaSel (Just Symbol "_gsqTimeoutInSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) ((:*:) (S1 (MetaSel (Just Symbol "_gsqDestinations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [GameSessionQueueDestination]))) (S1 (MetaSel (Just Symbol "_gsqName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

gameSessionQueue :: GameSessionQueue Source #

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

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

  • gsqGameSessionQueueARN - Amazon Resource Name (ARN ) that is assigned to a game session queue and uniquely identifies it. Format is arn:aws:gamelift:region::fleet/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912 .
  • gsqPlayerLatencyPolicies - Collection of latency policies to apply when processing game sessions placement requests with player latency information. Multiple policies are evaluated in order of the maximum latency value, starting with the lowest latency values. With just one policy, it is enforced at the start of the game session placement for the duration period. With multiple policies, each policy is enforced consecutively for its duration period. For example, a queue might enforce a 60-second policy followed by a 120-second policy, and then no policy for the remainder of the placement.
  • gsqTimeoutInSeconds - Maximum time, in seconds, that a new game session placement request remains in the queue. When a request exceeds this time, the game session placement changes to a TIMED_OUT status.
  • gsqDestinations - List of fleets that can be used to fulfill game session placement requests in the queue. Fleets are identified by either a fleet ARN or a fleet alias ARN. Destinations are listed in default preference order.
  • gsqName - Descriptive label that is associated with game session queue. Queue names must be unique within each region.

gsqGameSessionQueueARN :: Lens' GameSessionQueue (Maybe Text) Source #

Amazon Resource Name (ARN ) that is assigned to a game session queue and uniquely identifies it. Format is arn:aws:gamelift:region::fleet/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912 .

gsqPlayerLatencyPolicies :: Lens' GameSessionQueue [PlayerLatencyPolicy] Source #

Collection of latency policies to apply when processing game sessions placement requests with player latency information. Multiple policies are evaluated in order of the maximum latency value, starting with the lowest latency values. With just one policy, it is enforced at the start of the game session placement for the duration period. With multiple policies, each policy is enforced consecutively for its duration period. For example, a queue might enforce a 60-second policy followed by a 120-second policy, and then no policy for the remainder of the placement.

gsqTimeoutInSeconds :: Lens' GameSessionQueue (Maybe Natural) Source #

Maximum time, in seconds, that a new game session placement request remains in the queue. When a request exceeds this time, the game session placement changes to a TIMED_OUT status.

gsqDestinations :: Lens' GameSessionQueue [GameSessionQueueDestination] Source #

List of fleets that can be used to fulfill game session placement requests in the queue. Fleets are identified by either a fleet ARN or a fleet alias ARN. Destinations are listed in default preference order.

gsqName :: Lens' GameSessionQueue (Maybe Text) Source #

Descriptive label that is associated with game session queue. Queue names must be unique within each region.

GameSessionQueueDestination

data GameSessionQueueDestination Source #

Fleet designated in a game session queue. Requests for new game sessions in the queue are fulfilled by starting a new game session on any destination configured for a queue.

Queue-related operations include:

  • CreateGameSessionQueue
  • DescribeGameSessionQueues
  • UpdateGameSessionQueue
  • DeleteGameSessionQueue

See: gameSessionQueueDestination smart constructor.

Instances

Eq GameSessionQueueDestination Source # 
Data GameSessionQueueDestination Source # 

Methods

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

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

toConstr :: GameSessionQueueDestination -> Constr #

dataTypeOf :: GameSessionQueueDestination -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GameSessionQueueDestination Source # 
Show GameSessionQueueDestination Source # 
Generic GameSessionQueueDestination Source # 
Hashable GameSessionQueueDestination Source # 
FromJSON GameSessionQueueDestination Source # 
ToJSON GameSessionQueueDestination Source # 
NFData GameSessionQueueDestination Source # 
type Rep GameSessionQueueDestination Source # 
type Rep GameSessionQueueDestination = D1 (MetaData "GameSessionQueueDestination" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" True) (C1 (MetaCons "GameSessionQueueDestination'" PrefixI True) (S1 (MetaSel (Just Symbol "_gsqdDestinationARN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

gameSessionQueueDestination :: GameSessionQueueDestination Source #

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

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

  • gsqdDestinationARN - Amazon Resource Name (ARN) assigned to fleet or fleet alias. ARNs, which include a fleet ID or alias ID and a region name, provide a unique identifier across all regions.

gsqdDestinationARN :: Lens' GameSessionQueueDestination (Maybe Text) Source #

Amazon Resource Name (ARN) assigned to fleet or fleet alias. ARNs, which include a fleet ID or alias ID and a region name, provide a unique identifier across all regions.

IPPermission

data IPPermission Source #

A range of IP addresses and port settings that allow inbound traffic to connect to server processes on Amazon 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 # 
FromJSON IPPermission Source # 
ToJSON 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 may contain 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 (for example "1469498468.057").
  • iInstanceId - Unique identifier for an 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 run-time configuration. * ACTIVE -- The instance has been successfully created and at least one server process has successfully launched and reported back to Amazon 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 a fleet that the instance is in.

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 (for example "1469498468.057").

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

Unique identifier for an 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 run-time configuration. * ACTIVE -- The instance has been successfully created and at least one server process has successfully launched and reported back to Amazon 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 a fleet that the instance is in.

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 #

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.5.0-LWFsf2alHztGD91U7ab8u0" 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 an 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 a fleet containing the instance being accessed.

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

Unique identifier for an 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 a 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 #

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.5.0-LWFsf2alHztGD91U7ab8u0" 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 use with Windows Remote Desktop. For Linux instances, it is a private key (which must be saved as a .pem file) for use with SSH.

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

Secret string. For Windows instances, the secret is a password for use with Windows Remote Desktop. For Linux instances, it is a private key (which must be saved as a .pem file) for use with SSH.

MatchedPlayerSession

data MatchedPlayerSession Source #

Represents a new player session that is created as a result of a successful FlexMatch match. A successful match automatically creates new player sessions for every player ID in the original matchmaking request.

When players connect to the match's game session, they must include both player ID and player session ID in order to claim their assigned player slot.

See: matchedPlayerSession smart constructor.

Instances

Eq MatchedPlayerSession Source # 
Data MatchedPlayerSession Source # 

Methods

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

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

toConstr :: MatchedPlayerSession -> Constr #

dataTypeOf :: MatchedPlayerSession -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: MatchedPlayerSession -> () #

type Rep MatchedPlayerSession Source # 
type Rep MatchedPlayerSession = D1 (MetaData "MatchedPlayerSession" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "MatchedPlayerSession'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mpsPlayerSessionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mpsPlayerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

matchedPlayerSession :: MatchedPlayerSession Source #

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

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

mpsPlayerSessionId :: Lens' MatchedPlayerSession (Maybe Text) Source #

Unique identifier for a player session

mpsPlayerId :: Lens' MatchedPlayerSession (Maybe Text) Source #

Unique identifier for a player

MatchmakingConfiguration

data MatchmakingConfiguration Source #

Guidelines for use with FlexMatch to match players into games. All matchmaking requests must specify a matchmaking configuration.

See: matchmakingConfiguration smart constructor.

Instances

Eq MatchmakingConfiguration Source # 
Data MatchmakingConfiguration Source # 

Methods

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

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

toConstr :: MatchmakingConfiguration -> Constr #

dataTypeOf :: MatchmakingConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MatchmakingConfiguration Source # 
Show MatchmakingConfiguration Source # 
Generic MatchmakingConfiguration Source # 
Hashable MatchmakingConfiguration Source # 
FromJSON MatchmakingConfiguration Source # 
NFData MatchmakingConfiguration Source # 
type Rep MatchmakingConfiguration Source # 
type Rep MatchmakingConfiguration = D1 (MetaData "MatchmakingConfiguration" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "MatchmakingConfiguration'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mcCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) ((:*:) (S1 (MetaSel (Just Symbol "_mcGameProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [GameProperty]))) (S1 (MetaSel (Just Symbol "_mcRuleSetName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_mcAcceptanceTimeoutSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) ((:*:) (S1 (MetaSel (Just Symbol "_mcRequestTimeoutSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_mcNotificationTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mcGameSessionQueueARNs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_mcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mcCustomEventData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mcAcceptanceRequired") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_mcGameSessionData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_mcDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mcAdditionalPlayerCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))))

matchmakingConfiguration :: MatchmakingConfiguration Source #

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

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

  • mcCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • mcGameProperties - Set of developer-defined properties for a game session, formatted as a set of type:value pairs. These properties are included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ). This information is added to the new GameSession object that is created for a successful match.
  • mcRuleSetName - Unique identifier for a matchmaking rule set to use with this configuration. A matchmaking configuration can only use rule sets that are defined in the same region.
  • mcAcceptanceTimeoutSeconds - Length of time (in seconds) to wait for players to accept a proposed match. If any player rejects the match or fails to accept before the timeout, the ticket continues to look for an acceptable match.
  • mcRequestTimeoutSeconds - Maximum duration, in seconds, that a matchmaking ticket can remain in process before timing out. Requests that time out can be resubmitted as needed.
  • mcNotificationTarget - SNS topic ARN that is set up to receive matchmaking notifications.
  • mcGameSessionQueueARNs - Amazon Resource Name (ARN ) that is assigned to a game session queue and uniquely identifies it. Format is arn:aws:gamelift:region::fleet/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912 . These queues are used when placing game sessions for matches that are created with this matchmaking configuration. Queues can be located in any region.
  • mcName - Unique identifier for a matchmaking configuration. This name is used to identify the configuration associated with a matchmaking request or ticket.
  • mcCustomEventData - Information to attached to all events related to the matchmaking configuration.
  • mcAcceptanceRequired - Flag that determines whether or not a match that was created with this configuration must be accepted by the matched players. To require acceptance, set to TRUE.
  • mcGameSessionData - Set of developer-defined game session properties, formatted as a single string value. This data is included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ). This information is added to the new GameSession object that is created for a successful match.
  • mcDescription - Descriptive label that is associated with matchmaking configuration.
  • mcAdditionalPlayerCount - Number of player slots in a match to keep open for future players. For example, if the configuration's rule set specifies a match for a single 12-person team, and the additional player count is set to 2, only 10 players are selected for the match.

mcCreationTime :: Lens' MatchmakingConfiguration (Maybe UTCTime) Source #

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

mcGameProperties :: Lens' MatchmakingConfiguration [GameProperty] Source #

Set of developer-defined properties for a game session, formatted as a set of type:value pairs. These properties are included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ). This information is added to the new GameSession object that is created for a successful match.

mcRuleSetName :: Lens' MatchmakingConfiguration (Maybe Text) Source #

Unique identifier for a matchmaking rule set to use with this configuration. A matchmaking configuration can only use rule sets that are defined in the same region.

mcAcceptanceTimeoutSeconds :: Lens' MatchmakingConfiguration (Maybe Natural) Source #

Length of time (in seconds) to wait for players to accept a proposed match. If any player rejects the match or fails to accept before the timeout, the ticket continues to look for an acceptable match.

mcRequestTimeoutSeconds :: Lens' MatchmakingConfiguration (Maybe Natural) Source #

Maximum duration, in seconds, that a matchmaking ticket can remain in process before timing out. Requests that time out can be resubmitted as needed.

mcNotificationTarget :: Lens' MatchmakingConfiguration (Maybe Text) Source #

SNS topic ARN that is set up to receive matchmaking notifications.

mcGameSessionQueueARNs :: Lens' MatchmakingConfiguration [Text] Source #

Amazon Resource Name (ARN ) that is assigned to a game session queue and uniquely identifies it. Format is arn:aws:gamelift:region::fleet/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912 . These queues are used when placing game sessions for matches that are created with this matchmaking configuration. Queues can be located in any region.

mcName :: Lens' MatchmakingConfiguration (Maybe Text) Source #

Unique identifier for a matchmaking configuration. This name is used to identify the configuration associated with a matchmaking request or ticket.

mcCustomEventData :: Lens' MatchmakingConfiguration (Maybe Text) Source #

Information to attached to all events related to the matchmaking configuration.

mcAcceptanceRequired :: Lens' MatchmakingConfiguration (Maybe Bool) Source #

Flag that determines whether or not a match that was created with this configuration must be accepted by the matched players. To require acceptance, set to TRUE.

mcGameSessionData :: Lens' MatchmakingConfiguration (Maybe Text) Source #

Set of developer-defined game session properties, formatted as a single string value. This data is included in the GameSession object, which is passed to the game server with a request to start a new game session (see Start a Game Session ). This information is added to the new GameSession object that is created for a successful match.

mcDescription :: Lens' MatchmakingConfiguration (Maybe Text) Source #

Descriptive label that is associated with matchmaking configuration.

mcAdditionalPlayerCount :: Lens' MatchmakingConfiguration (Maybe Natural) Source #

Number of player slots in a match to keep open for future players. For example, if the configuration's rule set specifies a match for a single 12-person team, and the additional player count is set to 2, only 10 players are selected for the match.

MatchmakingRuleSet

data MatchmakingRuleSet Source #

Set of rule statements, used with FlexMatch, that determine how to build a certain kind of player match. Each rule set describes a type of group to be created and defines the parameters for acceptable player matches. Rule sets are used in MatchmakingConfiguration objects.

A rule set may define the following elements for a match. For detailed information and examples showing how to construct a rule set, see Create Matchmaking Rules for Your Game .

  • Teams -- Required. A rule set must define one or multiple teams for the match and set minimum and maximum team sizes. For example, a rule set might describe a 4x4 match that requires all eight slots to be filled.
  • Player attributes -- Optional. These attributes specify a set of player characteristics to evaluate when looking for a match. Matchmaking requests that use a rule set with player attributes must provide the corresponding attribute values. For example, an attribute might specify a player's skill or level.
  • Rules -- Optional. Rules define how to evaluate potential players for a match based on player attributes. A rule might specify minimum requirements for individual players--such as each player must meet a certain skill level, or may describe an entire group--such as all teams must be evenly matched or have at least one player in a certain role.
  • Expansions -- Optional. Expansions allow you to relax the rules after a period of time if no acceptable matches are found. This feature lets you balance getting players into games in a reasonable amount of time instead of making them wait indefinitely for the best possible match. For example, you might use an expansion to increase the maximum skill variance between players after 30 seconds.

See: matchmakingRuleSet smart constructor.

Instances

Eq MatchmakingRuleSet Source # 
Data MatchmakingRuleSet Source # 

Methods

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

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

toConstr :: MatchmakingRuleSet -> Constr #

dataTypeOf :: MatchmakingRuleSet -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: MatchmakingRuleSet -> () #

type Rep MatchmakingRuleSet Source # 
type Rep MatchmakingRuleSet = D1 (MetaData "MatchmakingRuleSet" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "MatchmakingRuleSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mrsCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) ((:*:) (S1 (MetaSel (Just Symbol "_mrsRuleSetName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mrsRuleSetBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

matchmakingRuleSet Source #

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

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

  • mrsCreationTime - Time stamp indicating when this data object was created. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • mrsRuleSetName - Unique identifier for a matchmaking rule set
  • mrsRuleSetBody - Collection of matchmaking rules, formatted as a JSON string. (Note that comments14 are not allowed in JSON, but most elements support a description field.)

mrsCreationTime :: Lens' MatchmakingRuleSet (Maybe UTCTime) Source #

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

mrsRuleSetName :: Lens' MatchmakingRuleSet (Maybe Text) Source #

Unique identifier for a matchmaking rule set

mrsRuleSetBody :: Lens' MatchmakingRuleSet Text Source #

Collection of matchmaking rules, formatted as a JSON string. (Note that comments14 are not allowed in JSON, but most elements support a description field.)

MatchmakingTicket

data MatchmakingTicket Source #

Ticket generated to track the progress of a matchmaking request. Each ticket is uniquely identified by a ticket ID, supplied by the requester, when creating a matchmaking request with StartMatchmaking . Tickets can be retrieved by calling DescribeMatchmaking with the ticket ID.

See: matchmakingTicket smart constructor.

Instances

Eq MatchmakingTicket Source # 
Data MatchmakingTicket Source # 

Methods

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

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

toConstr :: MatchmakingTicket -> Constr #

dataTypeOf :: MatchmakingTicket -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: MatchmakingTicket -> () #

type Rep MatchmakingTicket Source # 

matchmakingTicket :: MatchmakingTicket Source #

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

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

  • mtStatus - Current status of the matchmaking request. * QUEUED -- The matchmaking request has been received and is currently waiting to be processed. * SEARCHING -- The matchmaking request is currently being processed. * REQUIRES_ACCEPTANCE -- A match has been proposed and the players must accept the match (see AcceptMatch ). This status is used only with requests that use a matchmaking configuration with a player acceptance requirement. * PLACING -- The FlexMatch engine has matched players and is in the process of placing a new game session for the match. * COMPLETED -- Players have been matched and a game session is ready to host the players. A ticket in this state contains the necessary connection information for players. * FAILED -- The matchmaking request was not completed. Tickets with players who fail to accept a proposed match are placed in FAILED status; new matchmaking requests can be submitted for these players. * CANCELLED -- The matchmaking request was canceled with a call to StopMatchmaking . * TIMED_OUT -- The matchmaking request was not completed within the duration specified in the matchmaking configuration. Matchmaking requests that time out can be resubmitted.
  • mtConfigurationName - Name of the MatchmakingConfiguration that is used with this ticket. Matchmaking configurations determine how players are grouped into a match and how a new game session is created for the match.
  • mtStartTime - Time stamp indicating when this matchmaking request was received. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • mtGameSessionConnectionInfo - Identifier and connection information of the game session created for the match. This information is added to the ticket only after the matchmaking request has been successfully completed.
  • mtTicketId - Unique identifier for a matchmaking ticket.
  • mtEstimatedWaitTime - Average amount of time (in seconds) that players are currently waiting for a match. If there is not enough recent data, this property may be empty.
  • mtStatusMessage - Additional information about the current status.
  • mtEndTime - Time stamp indicating when the matchmaking request stopped being processed due to successful completion, timeout, or cancellation. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • mtStatusReason - Code to explain the current status. For example, a status reason may indicate when a ticket has returned to SEARCHING status after a proposed match fails to receive player acceptances.
  • mtPlayers - A set of Player objects, each representing a player to find matches for. Players are identified by a unique player ID and may include latency data for use during matchmaking. If the ticket is in status COMPLETED , the Player objects include the team the players were assigned to in the resulting match.

mtStatus :: Lens' MatchmakingTicket (Maybe MatchmakingConfigurationStatus) Source #

Current status of the matchmaking request. * QUEUED -- The matchmaking request has been received and is currently waiting to be processed. * SEARCHING -- The matchmaking request is currently being processed. * REQUIRES_ACCEPTANCE -- A match has been proposed and the players must accept the match (see AcceptMatch ). This status is used only with requests that use a matchmaking configuration with a player acceptance requirement. * PLACING -- The FlexMatch engine has matched players and is in the process of placing a new game session for the match. * COMPLETED -- Players have been matched and a game session is ready to host the players. A ticket in this state contains the necessary connection information for players. * FAILED -- The matchmaking request was not completed. Tickets with players who fail to accept a proposed match are placed in FAILED status; new matchmaking requests can be submitted for these players. * CANCELLED -- The matchmaking request was canceled with a call to StopMatchmaking . * TIMED_OUT -- The matchmaking request was not completed within the duration specified in the matchmaking configuration. Matchmaking requests that time out can be resubmitted.

mtConfigurationName :: Lens' MatchmakingTicket (Maybe Text) Source #

Name of the MatchmakingConfiguration that is used with this ticket. Matchmaking configurations determine how players are grouped into a match and how a new game session is created for the match.

mtStartTime :: Lens' MatchmakingTicket (Maybe UTCTime) Source #

Time stamp indicating when this matchmaking request was received. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").

mtGameSessionConnectionInfo :: Lens' MatchmakingTicket (Maybe GameSessionConnectionInfo) Source #

Identifier and connection information of the game session created for the match. This information is added to the ticket only after the matchmaking request has been successfully completed.

mtTicketId :: Lens' MatchmakingTicket (Maybe Text) Source #

Unique identifier for a matchmaking ticket.

mtEstimatedWaitTime :: Lens' MatchmakingTicket (Maybe Natural) Source #

Average amount of time (in seconds) that players are currently waiting for a match. If there is not enough recent data, this property may be empty.

mtStatusMessage :: Lens' MatchmakingTicket (Maybe Text) Source #

Additional information about the current status.

mtEndTime :: Lens' MatchmakingTicket (Maybe UTCTime) Source #

Time stamp indicating when the matchmaking request stopped being processed due to successful completion, timeout, or cancellation. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").

mtStatusReason :: Lens' MatchmakingTicket (Maybe Text) Source #

Code to explain the current status. For example, a status reason may indicate when a ticket has returned to SEARCHING status after a proposed match fails to receive player acceptances.

mtPlayers :: Lens' MatchmakingTicket [Player] Source #

A set of Player objects, each representing a player to find matches for. Players are identified by a unique player ID and may include latency data for use during matchmaking. If the ticket is in status COMPLETED , the Player objects include the team the players were assigned to in the resulting match.

PlacedPlayerSession

data PlacedPlayerSession Source #

Information about a player session that was created as part of a StartGameSessionPlacement request. This object contains only the player ID and player session ID. To retrieve full details on a player session, call DescribePlayerSessions with the player session ID.

Player-session-related operations include:

  • CreatePlayerSession
  • CreatePlayerSessions
  • DescribePlayerSessions
  • Game session placements
  • StartGameSessionPlacement
  • DescribeGameSessionPlacement
  • StopGameSessionPlacement

See: placedPlayerSession smart constructor.

Instances

Eq PlacedPlayerSession Source # 
Data PlacedPlayerSession Source # 

Methods

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

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

toConstr :: PlacedPlayerSession -> Constr #

dataTypeOf :: PlacedPlayerSession -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: PlacedPlayerSession -> () #

type Rep PlacedPlayerSession Source # 
type Rep PlacedPlayerSession = D1 (MetaData "PlacedPlayerSession" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "PlacedPlayerSession'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ppsPlayerSessionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ppsPlayerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

placedPlayerSession :: PlacedPlayerSession Source #

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

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

  • ppsPlayerSessionId - Unique identifier for a player session.
  • ppsPlayerId - Unique identifier for a player that is associated with this player session.

ppsPlayerSessionId :: Lens' PlacedPlayerSession (Maybe Text) Source #

Unique identifier for a player session.

ppsPlayerId :: Lens' PlacedPlayerSession (Maybe Text) Source #

Unique identifier for a player that is associated with this player session.

Player

data Player Source #

Represents a player in matchmaking. When starting a matchmaking request, a player has a player ID, attributes, and may have latency data. Team information is added after a match has been successfully completed.

See: player smart constructor.

Instances

Eq Player Source # 

Methods

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

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

Data Player Source # 

Methods

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

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

toConstr :: Player -> Constr #

dataTypeOf :: Player -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Player Source # 
Show Player Source # 
Generic Player Source # 

Associated Types

type Rep Player :: * -> * #

Methods

from :: Player -> Rep Player x #

to :: Rep Player x -> Player #

Hashable Player Source # 

Methods

hashWithSalt :: Int -> Player -> Int #

hash :: Player -> Int #

FromJSON Player Source # 
ToJSON Player Source # 
NFData Player Source # 

Methods

rnf :: Player -> () #

type Rep Player Source # 
type Rep Player = D1 (MetaData "Player" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "Player'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pPlayerAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text AttributeValue)))) (S1 (MetaSel (Just Symbol "_pTeam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_pPlayerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pLatencyInMs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Nat)))))))

player :: Player Source #

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

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

  • pPlayerAttributes - Collection of name:value pairs containing player information for use in matchmaking. Player attribute names need to match playerAttributes names in the rule set being used. Example: PlayerAttributes: {"skill": {N: "23"}, "gameMode": {S: "deathmatch"}} .
  • pTeam - Name of the team that the player is assigned to in a match. Team names are defined in a matchmaking rule set.
  • pPlayerId - Unique identifier for a player
  • pLatencyInMs - Set of values, expressed in milliseconds, indicating the amount of latency that a player experiences when connected to AWS regions. If this property is present, FlexMatch considers placing the match only in regions for which latency is reported. If a matchmaker has a rule that evaluates player latency, players must report latency in order to be matched. If no latency is reported in this scenario, FlexMatch assumes that no regions are available to the player and the ticket is not matchable.

pPlayerAttributes :: Lens' Player (HashMap Text AttributeValue) Source #

Collection of name:value pairs containing player information for use in matchmaking. Player attribute names need to match playerAttributes names in the rule set being used. Example: PlayerAttributes: {"skill": {N: "23"}, "gameMode": {S: "deathmatch"}} .

pTeam :: Lens' Player (Maybe Text) Source #

Name of the team that the player is assigned to in a match. Team names are defined in a matchmaking rule set.

pPlayerId :: Lens' Player (Maybe Text) Source #

Unique identifier for a player

pLatencyInMs :: Lens' Player (HashMap Text Natural) Source #

Set of values, expressed in milliseconds, indicating the amount of latency that a player experiences when connected to AWS regions. If this property is present, FlexMatch considers placing the match only in regions for which latency is reported. If a matchmaker has a rule that evaluates player latency, players must report latency in order to be matched. If no latency is reported in this scenario, FlexMatch assumes that no regions are available to the player and the ticket is not matchable.

PlayerLatency

data PlayerLatency Source #

Regional latency information for a player, used when requesting a new game session with StartGameSessionPlacement . This value indicates the amount of time lag that exists when the player is connected to a fleet in the specified region. The relative difference between a player's latency values for multiple regions are used to determine which fleets are best suited to place a new game session for the player.

See: playerLatency smart constructor.

Instances

Eq PlayerLatency Source # 
Data PlayerLatency Source # 

Methods

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

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

toConstr :: PlayerLatency -> Constr #

dataTypeOf :: PlayerLatency -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PlayerLatency Source # 
Show PlayerLatency Source # 
Generic PlayerLatency Source # 

Associated Types

type Rep PlayerLatency :: * -> * #

Hashable PlayerLatency Source # 
FromJSON PlayerLatency Source # 
ToJSON PlayerLatency Source # 
NFData PlayerLatency Source # 

Methods

rnf :: PlayerLatency -> () #

type Rep PlayerLatency Source # 
type Rep PlayerLatency = D1 (MetaData "PlayerLatency" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "PlayerLatency'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_plLatencyInMilliseconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))) ((:*:) (S1 (MetaSel (Just Symbol "_plRegionIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_plPlayerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

playerLatency :: PlayerLatency Source #

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

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

  • plLatencyInMilliseconds - Amount of time that represents the time lag experienced by the player when connected to the specified region.
  • plRegionIdentifier - Name of the region that is associated with the latency value.
  • plPlayerId - Unique identifier for a player associated with the latency data.

plLatencyInMilliseconds :: Lens' PlayerLatency (Maybe Double) Source #

Amount of time that represents the time lag experienced by the player when connected to the specified region.

plRegionIdentifier :: Lens' PlayerLatency (Maybe Text) Source #

Name of the region that is associated with the latency value.

plPlayerId :: Lens' PlayerLatency (Maybe Text) Source #

Unique identifier for a player associated with the latency data.

PlayerLatencyPolicy

data PlayerLatencyPolicy Source #

Queue setting that determines the highest latency allowed for individual players when placing a game session. When a latency policy is in force, a game session cannot be placed at any destination in a region where a player is reporting latency higher than the cap. Latency policies are only enforced when the placement request contains player latency information.

Queue-related operations include:

  • CreateGameSessionQueue
  • DescribeGameSessionQueues
  • UpdateGameSessionQueue
  • DeleteGameSessionQueue

See: playerLatencyPolicy smart constructor.

Instances

Eq PlayerLatencyPolicy Source # 
Data PlayerLatencyPolicy Source # 

Methods

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

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

toConstr :: PlayerLatencyPolicy -> Constr #

dataTypeOf :: PlayerLatencyPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: PlayerLatencyPolicy -> () #

type Rep PlayerLatencyPolicy Source # 
type Rep PlayerLatencyPolicy = D1 (MetaData "PlayerLatencyPolicy" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "PlayerLatencyPolicy'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_plpPolicyDurationSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_plpMaximumIndividualPlayerLatencyMilliseconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)))))

playerLatencyPolicy :: PlayerLatencyPolicy Source #

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

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

  • plpPolicyDurationSeconds - The length of time, in seconds, that the policy is enforced while placing a new game session. A null value for this property means that the policy is enforced until the queue times out.
  • plpMaximumIndividualPlayerLatencyMilliseconds - The maximum latency value that is allowed for any player, in milliseconds. All policies must have a value set for this property.

plpPolicyDurationSeconds :: Lens' PlayerLatencyPolicy (Maybe Natural) Source #

The length of time, in seconds, that the policy is enforced while placing a new game session. A null value for this property means that the policy is enforced until the queue times out.

plpMaximumIndividualPlayerLatencyMilliseconds :: Lens' PlayerLatencyPolicy (Maybe Natural) Source #

The maximum latency value that is allowed for any player, in milliseconds. All policies must have a value set for this property.

PlayerSession

data PlayerSession Source #

Properties describing a player session. Player session objects are created either by creating a player session for a specific game session, or as part of a game session placement. A player session represents either a player reservation for a game session (status RESERVED ) or actual player activity in a game session (status ACTIVE ). A player session object (including player data) is automatically passed to a game session when the player connects to the game session and is validated.

When a player disconnects, the player session status changes to COMPLETED . Once the session ends, the player session object is retained for 30 days and then removed.

Player-session-related operations include:

  • CreatePlayerSession
  • CreatePlayerSessions
  • DescribePlayerSessions
  • Game session placements
  • StartGameSessionPlacement
  • DescribeGameSessionPlacement
  • StopGameSessionPlacement

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 (for example "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 timeout limit (60 seconds).
  • psIPAddress - IP address of the game session. To connect to a Amazon GameLift game server, an app needs both the IP address and port number.
  • 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 (for example "1469498468.057").
  • psPlayerSessionId - Unique identifier for a player session.
  • psFleetId - Unique identifier for a fleet that the player's game session is running on.
  • psPlayerData - Developer-defined information related to a player. Amazon GameLift does not use this data, so it can be formatted as needed for use in the game.
  • psPlayerId - Unique identifier for a player that is associated with this player session.
  • psPort - Port number for the game session. To connect to a Amazon 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 (for example "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 timeout limit (60 seconds).

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

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

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 (for example "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 that the player's game session is running on.

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

Developer-defined information related to a player. Amazon GameLift does not use this data, so it can be formatted as needed for use in the game.

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

Unique identifier for a player that is associated with this player session.

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

Port number for the game session. To connect to a Amazon 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, Amazon 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 # 
FromJSON ResourceCreationLimitPolicy Source # 
ToJSON ResourceCreationLimitPolicy Source # 
NFData ResourceCreationLimitPolicy Source # 
type Rep ResourceCreationLimitPolicy Source # 
type Rep ResourceCreationLimitPolicy = D1 (MetaData "ResourceCreationLimitPolicy" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" 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.

Fleet-related operations include:

  • CreateFleet
  • ListFleets
  • Describe fleets:
  • DescribeFleetAttributes
  • DescribeFleetPortSettings
  • DescribeFleetUtilization
  • DescribeRuntimeConfiguration
  • DescribeFleetEvents
  • Update fleets:
  • UpdateFleetAttributes
  • UpdateFleetCapacity
  • UpdateFleetPortSettings
  • UpdateRuntimeConfiguration
  • Manage fleet capacity:
  • DescribeFleetCapacity
  • UpdateFleetCapacity
  • PutScalingPolicy (automatic scaling)
  • DescribeScalingPolicies (automatic scaling)
  • DeleteScalingPolicy (automatic scaling)
  • DescribeEC2InstanceLimits
  • DeleteFleet

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 # 
FromJSON RoutingStrategy Source # 
ToJSON 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.5.0-LWFsf2alHztGD91U7ab8u0" 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 that the alias points to.

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 that the alias points to.

RuntimeConfiguration

data RuntimeConfiguration Source #

A collection of server process configurations that describe what processes to run on each instance in a fleet. All fleets must have a run-time configuration. Each instance in the fleet launches the server processes specified in the run-time configuration and launches new ones as existing processes end. Each instance regularly checks for an updated run-time configuration and follows the new instructions.

The run-time configuration enables the instances in a fleet to run multiple processes simultaneously. Potential scenarios are as follows: (1) Run multiple processes of a single game server executable to maximize usage of your hosting resources. (2) Run one or more processes of different build executables, such as your game server executable and a related program, or two or more different versions of a game server. (3) Run multiple processes of a single game server but with different launch parameters, for example to run one process on each instance in debug mode.

A Amazon GameLift instance is limited to 50 processes running simultaneously. A run-time configuration must specify fewer than this limit. To calculate the total number of processes specified in a run-time configuration, add the values of the ConcurrentExecutions parameter for each ServerProcess object in the run-time configuration.

Fleet-related operations include:

  • CreateFleet
  • ListFleets
  • Describe fleets:
  • DescribeFleetAttributes
  • DescribeFleetPortSettings
  • DescribeFleetUtilization
  • DescribeRuntimeConfiguration
  • DescribeFleetEvents
  • Update fleets:
  • UpdateFleetAttributes
  • UpdateFleetCapacity
  • UpdateFleetPortSettings
  • UpdateRuntimeConfiguration
  • Manage fleet capacity:
  • DescribeFleetCapacity
  • UpdateFleetCapacity
  • PutScalingPolicy (automatic scaling)
  • DescribeScalingPolicies (automatic scaling)
  • DeleteScalingPolicy (automatic scaling)
  • DescribeEC2InstanceLimits
  • DeleteFleet

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 # 
FromJSON RuntimeConfiguration Source # 
ToJSON 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.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "RuntimeConfiguration'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rcGameSessionActivationTimeoutSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) ((:*:) (S1 (MetaSel (Just Symbol "_rcServerProcesses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (List1 ServerProcess)))) (S1 (MetaSel (Just Symbol "_rcMaxConcurrentGameSessionActivations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))))

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:

  • rcGameSessionActivationTimeoutSeconds - Maximum amount of time (in seconds) that a game session can remain in status ACTIVATING . If the game session is not active before the timeout, activation is terminated and the game session status is changed to TERMINATED .
  • rcServerProcesses - Collection of server process configurations that describe which server processes to run on each instance in a fleet.
  • rcMaxConcurrentGameSessionActivations - Maximum number of game sessions with status ACTIVATING to allow on an instance simultaneously. This setting limits the amount of instance resources that can be used for new game activations at any one time.

rcGameSessionActivationTimeoutSeconds :: Lens' RuntimeConfiguration (Maybe Natural) Source #

Maximum amount of time (in seconds) that a game session can remain in status ACTIVATING . If the game session is not active before the timeout, activation is terminated and the game session status is changed to TERMINATED .

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

Collection of server process configurations that describe which server processes to run on each instance in a fleet.

rcMaxConcurrentGameSessionActivations :: Lens' RuntimeConfiguration (Maybe Natural) Source #

Maximum number of game sessions with status ACTIVATING to allow on an instance simultaneously. This setting limits the amount of instance resources that can be used for new game activations at any one time.

S3Location

data S3Location Source #

Location in Amazon Simple Storage Service (Amazon S3) where build files can be stored for access by Amazon GameLift. This location is specified in a CreateBuild request. For more details, see the Create a Build with Files in Amazon S3 .

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 # 
FromJSON S3Location Source # 
ToJSON 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.5.0-LWFsf2alHztGD91U7ab8u0" 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. This is the name of your S3 bucket.
  • slKey - Name of the zip file containing your build files.
  • slRoleARN - Amazon Resource Name (ARN ) for the access role that allows Amazon GameLift to access your S3 bucket.

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

Amazon S3 bucket identifier. This is the name of your S3 bucket.

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

Name of the zip file containing your build files.

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

Amazon Resource Name (ARN ) for the access role that allows Amazon GameLift to access your 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.

Fleet-related operations include:

  • CreateFleet
  • ListFleets
  • Describe fleets:
  • DescribeFleetAttributes
  • DescribeFleetPortSettings
  • DescribeFleetUtilization
  • DescribeRuntimeConfiguration
  • DescribeFleetEvents
  • Update fleets:
  • UpdateFleetAttributes
  • UpdateFleetCapacity
  • UpdateFleetPortSettings
  • UpdateRuntimeConfiguration
  • Manage fleet capacity:
  • DescribeFleetCapacity
  • UpdateFleetCapacity
  • PutScalingPolicy (automatic scaling)
  • DescribeScalingPolicies (automatic scaling)
  • DeleteScalingPolicy (automatic scaling)
  • DescribeEC2InstanceLimits
  • DeleteFleet

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 Amazon 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 that is 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 identifier for a fleet that is 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 Amazon 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 that is 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 identifier for a fleet that is 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 # 
FromJSON ServerProcess Source # 
ToJSON 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.5.0-LWFsf2alHztGD91U7ab8u0" 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.

VPCPeeringAuthorization

data VPCPeeringAuthorization Source #

Represents an authorization for a VPC peering connection between the VPC for an Amazon GameLift fleet and another VPC on an account you have access to. This authorization must exist and be valid for the peering connection to be established. Authorizations are valid for 24 hours after they are issued.

VPC peering connection operations include:

  • CreateVpcPeeringAuthorization
  • DescribeVpcPeeringAuthorizations
  • DeleteVpcPeeringAuthorization
  • CreateVpcPeeringConnection
  • DescribeVpcPeeringConnections
  • DeleteVpcPeeringConnection

See: vpcPeeringAuthorization smart constructor.

Instances

Eq VPCPeeringAuthorization Source # 
Data VPCPeeringAuthorization Source # 

Methods

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

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

toConstr :: VPCPeeringAuthorization -> Constr #

dataTypeOf :: VPCPeeringAuthorization -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: VPCPeeringAuthorization -> () #

type Rep VPCPeeringAuthorization Source # 
type Rep VPCPeeringAuthorization = D1 (MetaData "VPCPeeringAuthorization" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "VPCPeeringAuthorization'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vpaCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) (S1 (MetaSel (Just Symbol "_vpaPeerVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_vpaPeerVPCAWSAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_vpaGameLiftAWSAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vpaExpirationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))))))

vpcPeeringAuthorization :: VPCPeeringAuthorization Source #

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

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

  • vpaCreationTime - Time stamp indicating when this authorization was issued. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").
  • vpaPeerVPCId - Unique identifier for a VPC with resources to be accessed by your Amazon GameLift fleet. The VPC must be in the same region where your fleet is deployed. To get VPC information, including IDs, use the Virtual Private Cloud service tools, including the VPC Dashboard in the AWS Management Console.
  • vpaPeerVPCAWSAccountId -
  • vpaGameLiftAWSAccountId - Unique identifier for the AWS account that you use to manage your Amazon GameLift fleet. You can find your Account ID in the AWS Management Console under account settings.
  • vpaExpirationTime - Time stamp indicating when this authorization expires (24 hours after issuance). Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").

vpaCreationTime :: Lens' VPCPeeringAuthorization (Maybe UTCTime) Source #

Time stamp indicating when this authorization was issued. Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").

vpaPeerVPCId :: Lens' VPCPeeringAuthorization (Maybe Text) Source #

Unique identifier for a VPC with resources to be accessed by your Amazon GameLift fleet. The VPC must be in the same region where your fleet is deployed. To get VPC information, including IDs, use the Virtual Private Cloud service tools, including the VPC Dashboard in the AWS Management Console.

vpaGameLiftAWSAccountId :: Lens' VPCPeeringAuthorization (Maybe Text) Source #

Unique identifier for the AWS account that you use to manage your Amazon GameLift fleet. You can find your Account ID in the AWS Management Console under account settings.

vpaExpirationTime :: Lens' VPCPeeringAuthorization (Maybe UTCTime) Source #

Time stamp indicating when this authorization expires (24 hours after issuance). Format is a number expressed in Unix time as milliseconds (for example "1469498468.057").

VPCPeeringConnection

data VPCPeeringConnection Source #

Represents a peering connection between a VPC on one of your AWS accounts and the VPC for your Amazon GameLift fleets. This record may be for an active peering connection or a pending connection that has not yet been established.

VPC peering connection operations include:

  • CreateVpcPeeringAuthorization
  • DescribeVpcPeeringAuthorizations
  • DeleteVpcPeeringAuthorization
  • CreateVpcPeeringConnection
  • DescribeVpcPeeringConnections
  • DeleteVpcPeeringConnection

See: vpcPeeringConnection smart constructor.

Instances

Eq VPCPeeringConnection Source # 
Data VPCPeeringConnection Source # 

Methods

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

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

toConstr :: VPCPeeringConnection -> Constr #

dataTypeOf :: VPCPeeringConnection -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: VPCPeeringConnection -> () #

type Rep VPCPeeringConnection Source # 
type Rep VPCPeeringConnection = D1 (MetaData "VPCPeeringConnection" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "VPCPeeringConnection'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vpcVPCPeeringConnectionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_vpcStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VPCPeeringConnectionStatus))) (S1 (MetaSel (Just Symbol "_vpcPeerVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_vpcIPV4CidrBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_vpcGameLiftVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vpcFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

vpcPeeringConnection :: VPCPeeringConnection Source #

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

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

  • vpcVPCPeeringConnectionId - Unique identifier that is automatically assigned to the connection record. This ID is referenced in VPC peering connection events, and is used when deleting a connection with DeleteVpcPeeringConnection .
  • vpcStatus - Object that contains status information about the connection. Status indicates if a connection is pending, successful, or failed.
  • vpcPeerVPCId - Unique identifier for a VPC with resources to be accessed by your Amazon GameLift fleet. The VPC must be in the same region where your fleet is deployed. To get VPC information, including IDs, use the Virtual Private Cloud service tools, including the VPC Dashboard in the AWS Management Console.
  • vpcIPV4CidrBlock - CIDR block of IPv4 addresses assigned to the VPC peering connection for the GameLift VPC. The peered VPC also has an IPv4 CIDR block associated with it; these blocks cannot overlap or the peering connection cannot be created.
  • vpcGameLiftVPCId - Unique identifier for the VPC that contains the Amazon GameLift fleet for this connection. This VPC is managed by Amazon GameLift and does not appear in your AWS account.
  • vpcFleetId - Unique identifier for a fleet. This ID determines the ID of the Amazon GameLift VPC for your fleet.

vpcVPCPeeringConnectionId :: Lens' VPCPeeringConnection (Maybe Text) Source #

Unique identifier that is automatically assigned to the connection record. This ID is referenced in VPC peering connection events, and is used when deleting a connection with DeleteVpcPeeringConnection .

vpcStatus :: Lens' VPCPeeringConnection (Maybe VPCPeeringConnectionStatus) Source #

Object that contains status information about the connection. Status indicates if a connection is pending, successful, or failed.

vpcPeerVPCId :: Lens' VPCPeeringConnection (Maybe Text) Source #

Unique identifier for a VPC with resources to be accessed by your Amazon GameLift fleet. The VPC must be in the same region where your fleet is deployed. To get VPC information, including IDs, use the Virtual Private Cloud service tools, including the VPC Dashboard in the AWS Management Console.

vpcIPV4CidrBlock :: Lens' VPCPeeringConnection (Maybe Text) Source #

CIDR block of IPv4 addresses assigned to the VPC peering connection for the GameLift VPC. The peered VPC also has an IPv4 CIDR block associated with it; these blocks cannot overlap or the peering connection cannot be created.

vpcGameLiftVPCId :: Lens' VPCPeeringConnection (Maybe Text) Source #

Unique identifier for the VPC that contains the Amazon GameLift fleet for this connection. This VPC is managed by Amazon GameLift and does not appear in your AWS account.

vpcFleetId :: Lens' VPCPeeringConnection (Maybe Text) Source #

Unique identifier for a fleet. This ID determines the ID of the Amazon GameLift VPC for your fleet.

VPCPeeringConnectionStatus

data VPCPeeringConnectionStatus Source #

Represents status information for a VPC peering connection. Status is associated with a VpcPeeringConnection object. Status codes and messages are provided from EC2 (). Connection status information is also communicated as a fleet Event .

See: vpcPeeringConnectionStatus smart constructor.

Instances

Eq VPCPeeringConnectionStatus Source # 
Data VPCPeeringConnectionStatus Source # 

Methods

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

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

toConstr :: VPCPeeringConnectionStatus -> Constr #

dataTypeOf :: VPCPeeringConnectionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read VPCPeeringConnectionStatus Source # 
Show VPCPeeringConnectionStatus Source # 
Generic VPCPeeringConnectionStatus Source # 
Hashable VPCPeeringConnectionStatus Source # 
FromJSON VPCPeeringConnectionStatus Source # 
NFData VPCPeeringConnectionStatus Source # 
type Rep VPCPeeringConnectionStatus Source # 
type Rep VPCPeeringConnectionStatus = D1 (MetaData "VPCPeeringConnectionStatus" "Network.AWS.GameLift.Types.Product" "amazonka-gamelift-1.5.0-LWFsf2alHztGD91U7ab8u0" False) (C1 (MetaCons "VPCPeeringConnectionStatus'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_vpcsCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vpcsMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

vpcPeeringConnectionStatus :: VPCPeeringConnectionStatus Source #

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

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

  • vpcsCode - Code indicating the status of a VPC peering connection.
  • vpcsMessage - Additional messaging associated with the connection status.

vpcsCode :: Lens' VPCPeeringConnectionStatus (Maybe Text) Source #

Code indicating the status of a VPC peering connection.

vpcsMessage :: Lens' VPCPeeringConnectionStatus (Maybe Text) Source #

Additional messaging associated with the connection status.