amazonka-emr-1.6.0: Amazon Elastic MapReduce SDK.

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

Network.AWS.EMR.Types

Contents

Description

 

Synopsis

Service Configuration

emr :: Service Source #

API version 2009-03-31 of the Amazon Elastic MapReduce SDK configuration.

Errors

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

This exception occurs when there is something wrong with user input.

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

Indicates that an error occurred while processing the request and that the request was not completed.

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

This exception occurs when there is an internal failure in the EMR service.

ActionOnFailure

data ActionOnFailure Source #

Instances

Bounded ActionOnFailure Source # 
Enum ActionOnFailure Source # 
Eq ActionOnFailure Source # 
Data ActionOnFailure Source # 

Methods

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

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

toConstr :: ActionOnFailure -> Constr #

dataTypeOf :: ActionOnFailure -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ActionOnFailure -> () #

ToHeader ActionOnFailure Source # 
ToQuery ActionOnFailure Source # 
ToByteString ActionOnFailure Source # 
FromText ActionOnFailure Source # 
ToText ActionOnFailure Source # 
type Rep ActionOnFailure Source # 
type Rep ActionOnFailure = D1 * (MetaData "ActionOnFailure" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CancelAndWait" PrefixI False) (U1 *)) (C1 * (MetaCons "Continue" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TerminateCluster" PrefixI False) (U1 *)) (C1 * (MetaCons "TerminateJobFlow" PrefixI False) (U1 *))))

AdjustmentType

data AdjustmentType Source #

Instances

Bounded AdjustmentType Source # 
Enum AdjustmentType Source # 
Eq AdjustmentType Source # 
Data AdjustmentType Source # 

Methods

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

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

toConstr :: AdjustmentType -> Constr #

dataTypeOf :: AdjustmentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AdjustmentType Source # 
Read AdjustmentType Source # 
Show AdjustmentType Source # 
Generic AdjustmentType Source # 

Associated Types

type Rep AdjustmentType :: * -> * #

Hashable AdjustmentType Source # 
ToJSON AdjustmentType Source # 
FromJSON AdjustmentType Source # 
NFData AdjustmentType Source # 

Methods

rnf :: AdjustmentType -> () #

ToHeader AdjustmentType Source # 
ToQuery AdjustmentType Source # 
ToByteString AdjustmentType Source # 
FromText AdjustmentType Source # 
ToText AdjustmentType Source # 
type Rep AdjustmentType Source # 
type Rep AdjustmentType = D1 * (MetaData "AdjustmentType" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "ChangeInCapacity" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ExactCapacity" PrefixI False) (U1 *)) (C1 * (MetaCons "PercentChangeInCapacity" PrefixI False) (U1 *))))

AutoScalingPolicyState

data AutoScalingPolicyState Source #

Instances

Bounded AutoScalingPolicyState Source # 
Enum AutoScalingPolicyState Source # 
Eq AutoScalingPolicyState Source # 
Data AutoScalingPolicyState Source # 

Methods

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

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

toConstr :: AutoScalingPolicyState -> Constr #

dataTypeOf :: AutoScalingPolicyState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: AutoScalingPolicyState -> () #

ToHeader AutoScalingPolicyState Source # 
ToQuery AutoScalingPolicyState Source # 
ToByteString AutoScalingPolicyState Source # 
FromText AutoScalingPolicyState Source # 
ToText AutoScalingPolicyState Source # 
type Rep AutoScalingPolicyState Source # 
type Rep AutoScalingPolicyState = D1 * (MetaData "AutoScalingPolicyState" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Attached" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Attaching" PrefixI False) (U1 *)) (C1 * (MetaCons "Detached" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Detaching" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Failed" PrefixI False) (U1 *)) (C1 * (MetaCons "Pending" PrefixI False) (U1 *)))))

AutoScalingPolicyStateChangeReasonCode

data AutoScalingPolicyStateChangeReasonCode Source #

Instances

Bounded AutoScalingPolicyStateChangeReasonCode Source # 
Enum AutoScalingPolicyStateChangeReasonCode Source # 
Eq AutoScalingPolicyStateChangeReasonCode Source # 
Data AutoScalingPolicyStateChangeReasonCode Source # 

Methods

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

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

toConstr :: AutoScalingPolicyStateChangeReasonCode -> Constr #

dataTypeOf :: AutoScalingPolicyStateChangeReasonCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AutoScalingPolicyStateChangeReasonCode Source # 
Read AutoScalingPolicyStateChangeReasonCode Source # 
Show AutoScalingPolicyStateChangeReasonCode Source # 
Generic AutoScalingPolicyStateChangeReasonCode Source # 
Hashable AutoScalingPolicyStateChangeReasonCode Source # 
FromJSON AutoScalingPolicyStateChangeReasonCode Source # 
NFData AutoScalingPolicyStateChangeReasonCode Source # 
ToHeader AutoScalingPolicyStateChangeReasonCode Source # 
ToQuery AutoScalingPolicyStateChangeReasonCode Source # 
ToByteString AutoScalingPolicyStateChangeReasonCode Source # 
FromText AutoScalingPolicyStateChangeReasonCode Source # 
ToText AutoScalingPolicyStateChangeReasonCode Source # 
type Rep AutoScalingPolicyStateChangeReasonCode Source # 
type Rep AutoScalingPolicyStateChangeReasonCode = D1 * (MetaData "AutoScalingPolicyStateChangeReasonCode" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "CleanupFailure" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ProvisionFailure" PrefixI False) (U1 *)) (C1 * (MetaCons "UserRequest" PrefixI False) (U1 *))))

CancelStepsRequestStatus

data CancelStepsRequestStatus Source #

Constructors

CSRSFailed 
CSRSSubmitted 

Instances

Bounded CancelStepsRequestStatus Source # 
Enum CancelStepsRequestStatus Source # 
Eq CancelStepsRequestStatus Source # 
Data CancelStepsRequestStatus Source # 

Methods

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

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

toConstr :: CancelStepsRequestStatus -> Constr #

dataTypeOf :: CancelStepsRequestStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CancelStepsRequestStatus Source # 
Read CancelStepsRequestStatus Source # 
Show CancelStepsRequestStatus Source # 
Generic CancelStepsRequestStatus Source # 
Hashable CancelStepsRequestStatus Source # 
FromJSON CancelStepsRequestStatus Source # 
NFData CancelStepsRequestStatus Source # 
ToHeader CancelStepsRequestStatus Source # 
ToQuery CancelStepsRequestStatus Source # 
ToByteString CancelStepsRequestStatus Source # 
FromText CancelStepsRequestStatus Source # 
ToText CancelStepsRequestStatus Source # 
type Rep CancelStepsRequestStatus Source # 
type Rep CancelStepsRequestStatus = D1 * (MetaData "CancelStepsRequestStatus" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "CSRSFailed" PrefixI False) (U1 *)) (C1 * (MetaCons "CSRSSubmitted" PrefixI False) (U1 *)))

ClusterState

data ClusterState Source #

Instances

Bounded ClusterState Source # 
Enum ClusterState Source # 
Eq ClusterState Source # 
Data ClusterState Source # 

Methods

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

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

toConstr :: ClusterState -> Constr #

dataTypeOf :: ClusterState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClusterState Source # 
Read ClusterState Source # 
Show ClusterState Source # 
Generic ClusterState Source # 

Associated Types

type Rep ClusterState :: * -> * #

Hashable ClusterState Source # 
ToJSON ClusterState Source # 
FromJSON ClusterState Source # 
NFData ClusterState Source # 

Methods

rnf :: ClusterState -> () #

ToHeader ClusterState Source # 
ToQuery ClusterState Source # 
ToByteString ClusterState Source # 
FromText ClusterState Source # 
ToText ClusterState Source # 

Methods

toText :: ClusterState -> Text #

type Rep ClusterState Source # 
type Rep ClusterState = D1 * (MetaData "ClusterState" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CSBootstrapping" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CSRunning" PrefixI False) (U1 *)) (C1 * (MetaCons "CSStarting" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CSTerminated" PrefixI False) (U1 *)) (C1 * (MetaCons "CSTerminatedWithErrors" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CSTerminating" PrefixI False) (U1 *)) (C1 * (MetaCons "CSWaiting" PrefixI False) (U1 *)))))

ClusterStateChangeReasonCode

data ClusterStateChangeReasonCode Source #

Instances

Bounded ClusterStateChangeReasonCode Source # 
Enum ClusterStateChangeReasonCode Source # 
Eq ClusterStateChangeReasonCode Source # 
Data ClusterStateChangeReasonCode Source # 

Methods

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

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

toConstr :: ClusterStateChangeReasonCode -> Constr #

dataTypeOf :: ClusterStateChangeReasonCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClusterStateChangeReasonCode Source # 
Read ClusterStateChangeReasonCode Source # 
Show ClusterStateChangeReasonCode Source # 
Generic ClusterStateChangeReasonCode Source # 
Hashable ClusterStateChangeReasonCode Source # 
FromJSON ClusterStateChangeReasonCode Source # 
NFData ClusterStateChangeReasonCode Source # 
ToHeader ClusterStateChangeReasonCode Source # 
ToQuery ClusterStateChangeReasonCode Source # 
ToByteString ClusterStateChangeReasonCode Source # 
FromText ClusterStateChangeReasonCode Source # 
ToText ClusterStateChangeReasonCode Source # 
type Rep ClusterStateChangeReasonCode Source # 
type Rep ClusterStateChangeReasonCode = D1 * (MetaData "ClusterStateChangeReasonCode" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CSCRCAllStepsCompleted" PrefixI False) (U1 *)) (C1 * (MetaCons "CSCRCBootstrapFailure" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CSCRCInstanceFailure" PrefixI False) (U1 *)) (C1 * (MetaCons "CSCRCInstanceFleetTimeout" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CSCRCInternalError" PrefixI False) (U1 *)) (C1 * (MetaCons "CSCRCStepFailure" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CSCRCUserRequest" PrefixI False) (U1 *)) (C1 * (MetaCons "CSCRCValidationError" PrefixI False) (U1 *)))))

ComparisonOperator

data ComparisonOperator Source #

Instances

Bounded ComparisonOperator Source # 
Enum ComparisonOperator Source # 
Eq ComparisonOperator Source # 
Data ComparisonOperator Source # 

Methods

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

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

toConstr :: ComparisonOperator -> Constr #

dataTypeOf :: ComparisonOperator -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ComparisonOperator -> () #

ToHeader ComparisonOperator Source # 
ToQuery ComparisonOperator Source # 
ToByteString ComparisonOperator Source # 
FromText ComparisonOperator Source # 
ToText ComparisonOperator Source # 
type Rep ComparisonOperator Source # 
type Rep ComparisonOperator = D1 * (MetaData "ComparisonOperator" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "GreaterThan" PrefixI False) (U1 *)) (C1 * (MetaCons "GreaterThanOrEqual" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LessThan" PrefixI False) (U1 *)) (C1 * (MetaCons "LessThanOrEqual" PrefixI False) (U1 *))))

InstanceCollectionType

data InstanceCollectionType Source #

Instances

Bounded InstanceCollectionType Source # 
Enum InstanceCollectionType Source # 
Eq InstanceCollectionType Source # 
Data InstanceCollectionType Source # 

Methods

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

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

toConstr :: InstanceCollectionType -> Constr #

dataTypeOf :: InstanceCollectionType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceCollectionType -> () #

ToHeader InstanceCollectionType Source # 
ToQuery InstanceCollectionType Source # 
ToByteString InstanceCollectionType Source # 
FromText InstanceCollectionType Source # 
ToText InstanceCollectionType Source # 
type Rep InstanceCollectionType Source # 
type Rep InstanceCollectionType = D1 * (MetaData "InstanceCollectionType" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "InstanceFleet" PrefixI False) (U1 *)) (C1 * (MetaCons "InstanceGroup" PrefixI False) (U1 *)))

InstanceFleetState

data InstanceFleetState Source #

Instances

Bounded InstanceFleetState Source # 
Enum InstanceFleetState Source # 
Eq InstanceFleetState Source # 
Data InstanceFleetState Source # 

Methods

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

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

toConstr :: InstanceFleetState -> Constr #

dataTypeOf :: InstanceFleetState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceFleetState -> () #

ToHeader InstanceFleetState Source # 
ToQuery InstanceFleetState Source # 
ToByteString InstanceFleetState Source # 
FromText InstanceFleetState Source # 
ToText InstanceFleetState Source # 
type Rep InstanceFleetState Source # 
type Rep InstanceFleetState = D1 * (MetaData "InstanceFleetState" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "IFSBootstrapping" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IFSProvisioning" PrefixI False) (U1 *)) (C1 * (MetaCons "IFSResizing" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "IFSRunning" PrefixI False) (U1 *)) (C1 * (MetaCons "IFSSuspended" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "IFSTerminated" PrefixI False) (U1 *)) (C1 * (MetaCons "IFSTerminating" PrefixI False) (U1 *)))))

InstanceFleetStateChangeReasonCode

data InstanceFleetStateChangeReasonCode Source #

Instances

Bounded InstanceFleetStateChangeReasonCode Source # 
Enum InstanceFleetStateChangeReasonCode Source # 
Eq InstanceFleetStateChangeReasonCode Source # 
Data InstanceFleetStateChangeReasonCode Source # 

Methods

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

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

toConstr :: InstanceFleetStateChangeReasonCode -> Constr #

dataTypeOf :: InstanceFleetStateChangeReasonCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstanceFleetStateChangeReasonCode Source # 
Read InstanceFleetStateChangeReasonCode Source # 
Show InstanceFleetStateChangeReasonCode Source # 
Generic InstanceFleetStateChangeReasonCode Source # 
Hashable InstanceFleetStateChangeReasonCode Source # 
FromJSON InstanceFleetStateChangeReasonCode Source # 
NFData InstanceFleetStateChangeReasonCode Source # 
ToHeader InstanceFleetStateChangeReasonCode Source # 
ToQuery InstanceFleetStateChangeReasonCode Source # 
ToByteString InstanceFleetStateChangeReasonCode Source # 
FromText InstanceFleetStateChangeReasonCode Source # 
ToText InstanceFleetStateChangeReasonCode Source # 
type Rep InstanceFleetStateChangeReasonCode Source # 
type Rep InstanceFleetStateChangeReasonCode = D1 * (MetaData "InstanceFleetStateChangeReasonCode" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "IFSCRCClusterTerminated" PrefixI False) (U1 *)) (C1 * (MetaCons "IFSCRCInstanceFailure" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "IFSCRCInternalError" PrefixI False) (U1 *)) (C1 * (MetaCons "IFSCRCValidationError" PrefixI False) (U1 *))))

InstanceFleetType

data InstanceFleetType Source #

Constructors

IFTCore 
IFTMaster 
IFTTask 

Instances

Bounded InstanceFleetType Source # 
Enum InstanceFleetType Source # 
Eq InstanceFleetType Source # 
Data InstanceFleetType Source # 

Methods

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

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

toConstr :: InstanceFleetType -> Constr #

dataTypeOf :: InstanceFleetType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceFleetType -> () #

ToHeader InstanceFleetType Source # 
ToQuery InstanceFleetType Source # 
ToByteString InstanceFleetType Source # 
FromText InstanceFleetType Source # 
ToText InstanceFleetType Source # 
type Rep InstanceFleetType Source # 
type Rep InstanceFleetType = D1 * (MetaData "InstanceFleetType" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "IFTCore" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IFTMaster" PrefixI False) (U1 *)) (C1 * (MetaCons "IFTTask" PrefixI False) (U1 *))))

InstanceGroupState

data InstanceGroupState Source #

Instances

Bounded InstanceGroupState Source # 
Enum InstanceGroupState Source # 
Eq InstanceGroupState Source # 
Data InstanceGroupState Source # 

Methods

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

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

toConstr :: InstanceGroupState -> Constr #

dataTypeOf :: InstanceGroupState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceGroupState -> () #

ToHeader InstanceGroupState Source # 
ToQuery InstanceGroupState Source # 
ToByteString InstanceGroupState Source # 
FromText InstanceGroupState Source # 
ToText InstanceGroupState Source # 
type Rep InstanceGroupState Source # 
type Rep InstanceGroupState = D1 * (MetaData "InstanceGroupState" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Arrested" PrefixI False) (U1 *)) (C1 * (MetaCons "Bootstrapping" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Ended" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Provisioning" PrefixI False) (U1 *)) (C1 * (MetaCons "Resizing" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Running" PrefixI False) (U1 *)) (C1 * (MetaCons "ShuttingDown" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Suspended" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Terminated" PrefixI False) (U1 *)) (C1 * (MetaCons "Terminating" PrefixI False) (U1 *))))))

InstanceGroupStateChangeReasonCode

data InstanceGroupStateChangeReasonCode Source #

Instances

Bounded InstanceGroupStateChangeReasonCode Source # 
Enum InstanceGroupStateChangeReasonCode Source # 
Eq InstanceGroupStateChangeReasonCode Source # 
Data InstanceGroupStateChangeReasonCode Source # 

Methods

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

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

toConstr :: InstanceGroupStateChangeReasonCode -> Constr #

dataTypeOf :: InstanceGroupStateChangeReasonCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstanceGroupStateChangeReasonCode Source # 
Read InstanceGroupStateChangeReasonCode Source # 
Show InstanceGroupStateChangeReasonCode Source # 
Generic InstanceGroupStateChangeReasonCode Source # 
Hashable InstanceGroupStateChangeReasonCode Source # 
FromJSON InstanceGroupStateChangeReasonCode Source # 
NFData InstanceGroupStateChangeReasonCode Source # 
ToHeader InstanceGroupStateChangeReasonCode Source # 
ToQuery InstanceGroupStateChangeReasonCode Source # 
ToByteString InstanceGroupStateChangeReasonCode Source # 
FromText InstanceGroupStateChangeReasonCode Source # 
ToText InstanceGroupStateChangeReasonCode Source # 
type Rep InstanceGroupStateChangeReasonCode Source # 
type Rep InstanceGroupStateChangeReasonCode = D1 * (MetaData "InstanceGroupStateChangeReasonCode" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ClusterTerminated" PrefixI False) (U1 *)) (C1 * (MetaCons "InstanceFailure" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "InternalError" PrefixI False) (U1 *)) (C1 * (MetaCons "ValidationError" PrefixI False) (U1 *))))

InstanceGroupType

data InstanceGroupType Source #

Constructors

Core 
Master 
Task 

Instances

Bounded InstanceGroupType Source # 
Enum InstanceGroupType Source # 
Eq InstanceGroupType Source # 
Data InstanceGroupType Source # 

Methods

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

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

toConstr :: InstanceGroupType -> Constr #

dataTypeOf :: InstanceGroupType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceGroupType -> () #

ToHeader InstanceGroupType Source # 
ToQuery InstanceGroupType Source # 
ToByteString InstanceGroupType Source # 
FromText InstanceGroupType Source # 
ToText InstanceGroupType Source # 
type Rep InstanceGroupType Source # 
type Rep InstanceGroupType = D1 * (MetaData "InstanceGroupType" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "Core" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Master" PrefixI False) (U1 *)) (C1 * (MetaCons "Task" PrefixI False) (U1 *))))

InstanceRoleType

data InstanceRoleType Source #

Constructors

IRTCore 
IRTMaster 
IRTTask 

Instances

Bounded InstanceRoleType Source # 
Enum InstanceRoleType Source # 
Eq InstanceRoleType Source # 
Data InstanceRoleType Source # 

Methods

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

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

toConstr :: InstanceRoleType -> Constr #

dataTypeOf :: InstanceRoleType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceRoleType -> () #

ToHeader InstanceRoleType Source # 
ToQuery InstanceRoleType Source # 
ToByteString InstanceRoleType Source # 
FromText InstanceRoleType Source # 
ToText InstanceRoleType Source # 
type Rep InstanceRoleType Source # 
type Rep InstanceRoleType = D1 * (MetaData "InstanceRoleType" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "IRTCore" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IRTMaster" PrefixI False) (U1 *)) (C1 * (MetaCons "IRTTask" PrefixI False) (U1 *))))

InstanceState

data InstanceState Source #

Instances

Bounded InstanceState Source # 
Enum InstanceState Source # 
Eq InstanceState Source # 
Data InstanceState Source # 

Methods

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

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

toConstr :: InstanceState -> Constr #

dataTypeOf :: InstanceState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstanceState Source # 
Read InstanceState Source # 
Show InstanceState Source # 
Generic InstanceState Source # 

Associated Types

type Rep InstanceState :: * -> * #

Hashable InstanceState Source # 
ToJSON InstanceState Source # 
FromJSON InstanceState Source # 
NFData InstanceState Source # 

Methods

rnf :: InstanceState -> () #

ToHeader InstanceState Source # 
ToQuery InstanceState Source # 
ToByteString InstanceState Source # 
FromText InstanceState Source # 
ToText InstanceState Source # 

Methods

toText :: InstanceState -> Text #

type Rep InstanceState Source # 
type Rep InstanceState = D1 * (MetaData "InstanceState" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ISAwaitingFulfillment" PrefixI False) (U1 *)) (C1 * (MetaCons "ISBootstrapping" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ISProvisioning" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ISRunning" PrefixI False) (U1 *)) (C1 * (MetaCons "ISTerminated" PrefixI False) (U1 *)))))

InstanceStateChangeReasonCode

data InstanceStateChangeReasonCode Source #

Instances

Bounded InstanceStateChangeReasonCode Source # 
Enum InstanceStateChangeReasonCode Source # 
Eq InstanceStateChangeReasonCode Source # 
Data InstanceStateChangeReasonCode Source # 

Methods

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

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

toConstr :: InstanceStateChangeReasonCode -> Constr #

dataTypeOf :: InstanceStateChangeReasonCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstanceStateChangeReasonCode Source # 
Read InstanceStateChangeReasonCode Source # 
Show InstanceStateChangeReasonCode Source # 
Generic InstanceStateChangeReasonCode Source # 
Hashable InstanceStateChangeReasonCode Source # 
FromJSON InstanceStateChangeReasonCode Source # 
NFData InstanceStateChangeReasonCode Source # 
ToHeader InstanceStateChangeReasonCode Source # 
ToQuery InstanceStateChangeReasonCode Source # 
ToByteString InstanceStateChangeReasonCode Source # 
FromText InstanceStateChangeReasonCode Source # 
ToText InstanceStateChangeReasonCode Source # 
type Rep InstanceStateChangeReasonCode Source # 
type Rep InstanceStateChangeReasonCode = D1 * (MetaData "InstanceStateChangeReasonCode" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ISCRCBootstrapFailure" PrefixI False) (U1 *)) (C1 * (MetaCons "ISCRCClusterTerminated" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ISCRCInstanceFailure" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ISCRCInternalError" PrefixI False) (U1 *)) (C1 * (MetaCons "ISCRCValidationError" PrefixI False) (U1 *)))))

MarketType

data MarketType Source #

Constructors

OnDemand 
Spot 

Instances

Bounded MarketType Source # 
Enum MarketType Source # 
Eq MarketType Source # 
Data MarketType Source # 

Methods

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

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

toConstr :: MarketType -> Constr #

dataTypeOf :: MarketType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MarketType Source # 
Read MarketType Source # 
Show MarketType Source # 
Generic MarketType Source # 

Associated Types

type Rep MarketType :: * -> * #

Hashable MarketType Source # 
ToJSON MarketType Source # 
FromJSON MarketType Source # 
NFData MarketType Source # 

Methods

rnf :: MarketType -> () #

ToHeader MarketType Source # 
ToQuery MarketType Source # 
ToByteString MarketType Source # 
FromText MarketType Source # 
ToText MarketType Source # 

Methods

toText :: MarketType -> Text #

type Rep MarketType Source # 
type Rep MarketType = D1 * (MetaData "MarketType" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "OnDemand" PrefixI False) (U1 *)) (C1 * (MetaCons "Spot" PrefixI False) (U1 *)))

RepoUpgradeOnBoot

data RepoUpgradeOnBoot Source #

Constructors

RUOBNone 
RUOBSecurity 

Instances

Bounded RepoUpgradeOnBoot Source # 
Enum RepoUpgradeOnBoot Source # 
Eq RepoUpgradeOnBoot Source # 
Data RepoUpgradeOnBoot Source # 

Methods

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

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

toConstr :: RepoUpgradeOnBoot -> Constr #

dataTypeOf :: RepoUpgradeOnBoot -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: RepoUpgradeOnBoot -> () #

ToHeader RepoUpgradeOnBoot Source # 
ToQuery RepoUpgradeOnBoot Source # 
ToByteString RepoUpgradeOnBoot Source # 
FromText RepoUpgradeOnBoot Source # 
ToText RepoUpgradeOnBoot Source # 
type Rep RepoUpgradeOnBoot Source # 
type Rep RepoUpgradeOnBoot = D1 * (MetaData "RepoUpgradeOnBoot" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "RUOBNone" PrefixI False) (U1 *)) (C1 * (MetaCons "RUOBSecurity" PrefixI False) (U1 *)))

ScaleDownBehavior

data ScaleDownBehavior Source #

Instances

Bounded ScaleDownBehavior Source # 
Enum ScaleDownBehavior Source # 
Eq ScaleDownBehavior Source # 
Data ScaleDownBehavior Source # 

Methods

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

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

toConstr :: ScaleDownBehavior -> Constr #

dataTypeOf :: ScaleDownBehavior -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ScaleDownBehavior -> () #

ToHeader ScaleDownBehavior Source # 
ToQuery ScaleDownBehavior Source # 
ToByteString ScaleDownBehavior Source # 
FromText ScaleDownBehavior Source # 
ToText ScaleDownBehavior Source # 
type Rep ScaleDownBehavior Source # 
type Rep ScaleDownBehavior = D1 * (MetaData "ScaleDownBehavior" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "TerminateAtInstanceHour" PrefixI False) (U1 *)) (C1 * (MetaCons "TerminateAtTaskCompletion" PrefixI False) (U1 *)))

SpotProvisioningTimeoutAction

data SpotProvisioningTimeoutAction Source #

Instances

Bounded SpotProvisioningTimeoutAction Source # 
Enum SpotProvisioningTimeoutAction Source # 
Eq SpotProvisioningTimeoutAction Source # 
Data SpotProvisioningTimeoutAction Source # 

Methods

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

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

toConstr :: SpotProvisioningTimeoutAction -> Constr #

dataTypeOf :: SpotProvisioningTimeoutAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SpotProvisioningTimeoutAction Source # 
Read SpotProvisioningTimeoutAction Source # 
Show SpotProvisioningTimeoutAction Source # 
Generic SpotProvisioningTimeoutAction Source # 
Hashable SpotProvisioningTimeoutAction Source # 
ToJSON SpotProvisioningTimeoutAction Source # 
FromJSON SpotProvisioningTimeoutAction Source # 
NFData SpotProvisioningTimeoutAction Source # 
ToHeader SpotProvisioningTimeoutAction Source # 
ToQuery SpotProvisioningTimeoutAction Source # 
ToByteString SpotProvisioningTimeoutAction Source # 
FromText SpotProvisioningTimeoutAction Source # 
ToText SpotProvisioningTimeoutAction Source # 
type Rep SpotProvisioningTimeoutAction Source # 
type Rep SpotProvisioningTimeoutAction = D1 * (MetaData "SpotProvisioningTimeoutAction" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * (C1 * (MetaCons "SPTASwitchToOnDemand" PrefixI False) (U1 *)) (C1 * (MetaCons "SPTATerminateCluster" PrefixI False) (U1 *)))

Statistic

data Statistic Source #

Instances

Bounded Statistic Source # 
Enum Statistic Source # 
Eq Statistic Source # 
Data Statistic Source # 

Methods

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

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

toConstr :: Statistic -> Constr #

dataTypeOf :: Statistic -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Statistic Source # 
Read Statistic Source # 
Show Statistic Source # 
Generic Statistic Source # 

Associated Types

type Rep Statistic :: * -> * #

Hashable Statistic Source # 
ToJSON Statistic Source # 
FromJSON Statistic Source # 
NFData Statistic Source # 

Methods

rnf :: Statistic -> () #

ToHeader Statistic Source # 
ToQuery Statistic Source # 
ToByteString Statistic Source # 

Methods

toBS :: Statistic -> ByteString #

FromText Statistic Source # 
ToText Statistic Source # 

Methods

toText :: Statistic -> Text #

type Rep Statistic Source # 
type Rep Statistic = D1 * (MetaData "Statistic" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Average" PrefixI False) (U1 *)) (C1 * (MetaCons "Maximum" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Minimum" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SampleCount" PrefixI False) (U1 *)) (C1 * (MetaCons "Sum" PrefixI False) (U1 *)))))

StepState

data StepState Source #

Instances

Bounded StepState Source # 
Enum StepState Source # 
Eq StepState Source # 
Data StepState Source # 

Methods

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

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

toConstr :: StepState -> Constr #

dataTypeOf :: StepState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StepState Source # 
Read StepState Source # 
Show StepState Source # 
Generic StepState Source # 

Associated Types

type Rep StepState :: * -> * #

Hashable StepState Source # 
ToJSON StepState Source # 
FromJSON StepState Source # 
NFData StepState Source # 

Methods

rnf :: StepState -> () #

ToHeader StepState Source # 
ToQuery StepState Source # 
ToByteString StepState Source # 

Methods

toBS :: StepState -> ByteString #

FromText StepState Source # 
ToText StepState Source # 

Methods

toText :: StepState -> Text #

type Rep StepState Source # 
type Rep StepState = D1 * (MetaData "StepState" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SSCancelPending" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SSCancelled" PrefixI False) (U1 *)) (C1 * (MetaCons "SSCompleted" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "SSFailed" PrefixI False) (U1 *)) (C1 * (MetaCons "SSInterrupted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "SSPending" PrefixI False) (U1 *)) (C1 * (MetaCons "SSRunning" PrefixI False) (U1 *)))))

StepStateChangeReasonCode

data StepStateChangeReasonCode Source #

Constructors

SSCRCNone 

Instances

Bounded StepStateChangeReasonCode Source # 
Enum StepStateChangeReasonCode Source # 
Eq StepStateChangeReasonCode Source # 
Data StepStateChangeReasonCode Source # 

Methods

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

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

toConstr :: StepStateChangeReasonCode -> Constr #

dataTypeOf :: StepStateChangeReasonCode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StepStateChangeReasonCode Source # 
Read StepStateChangeReasonCode Source # 
Show StepStateChangeReasonCode Source # 
Generic StepStateChangeReasonCode Source # 
Hashable StepStateChangeReasonCode Source # 
FromJSON StepStateChangeReasonCode Source # 
NFData StepStateChangeReasonCode Source # 
ToHeader StepStateChangeReasonCode Source # 
ToQuery StepStateChangeReasonCode Source # 
ToByteString StepStateChangeReasonCode Source # 
FromText StepStateChangeReasonCode Source # 
ToText StepStateChangeReasonCode Source # 
type Rep StepStateChangeReasonCode Source # 
type Rep StepStateChangeReasonCode = D1 * (MetaData "StepStateChangeReasonCode" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "SSCRCNone" PrefixI False) (U1 *))

Unit

data Unit Source #

Instances

Bounded Unit Source # 
Enum Unit Source # 

Methods

succ :: Unit -> Unit #

pred :: Unit -> Unit #

toEnum :: Int -> Unit #

fromEnum :: Unit -> Int #

enumFrom :: Unit -> [Unit] #

enumFromThen :: Unit -> Unit -> [Unit] #

enumFromTo :: Unit -> Unit -> [Unit] #

enumFromThenTo :: Unit -> Unit -> Unit -> [Unit] #

Eq Unit Source # 

Methods

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

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

Data Unit Source # 

Methods

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

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

toConstr :: Unit -> Constr #

dataTypeOf :: Unit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Unit Source # 

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

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

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

Read Unit Source # 
Show Unit Source # 

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

Generic Unit Source # 

Associated Types

type Rep Unit :: * -> * #

Methods

from :: Unit -> Rep Unit x #

to :: Rep Unit x -> Unit #

Hashable Unit Source # 

Methods

hashWithSalt :: Int -> Unit -> Int #

hash :: Unit -> Int #

ToJSON Unit Source # 
FromJSON Unit Source # 
NFData Unit Source # 

Methods

rnf :: Unit -> () #

ToHeader Unit Source # 

Methods

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

ToQuery Unit Source # 

Methods

toQuery :: Unit -> QueryString #

ToByteString Unit Source # 

Methods

toBS :: Unit -> ByteString #

FromText Unit Source # 

Methods

parser :: Parser Unit #

ToText Unit Source # 

Methods

toText :: Unit -> Text #

type Rep Unit Source # 
type Rep Unit = D1 * (MetaData "Unit" "Network.AWS.EMR.Types.Sum" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Bits" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "BitsPerSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "Bytes" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "BytesPerSecond" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Count" PrefixI False) (U1 *)) (C1 * (MetaCons "CountPerSecond" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "GigaBits" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "GigaBitsPerSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "GigaBytes" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "GigaBytesPerSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "KiloBits" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KiloBitsPerSecond" PrefixI False) (U1 *)) (C1 * (MetaCons "KiloBytes" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "KiloBytesPerSecond" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MegaBits" PrefixI False) (U1 *)) (C1 * (MetaCons "MegaBitsPerSecond" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "MegaBytes" PrefixI False) (U1 *)) (C1 * (MetaCons "MegaBytesPerSecond" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MicroSeconds" PrefixI False) (U1 *)) (C1 * (MetaCons "MilliSeconds" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "None" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Percent" PrefixI False) (U1 *)) (C1 * (MetaCons "Seconds" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "TeraBits" PrefixI False) (U1 *)) (C1 * (MetaCons "TeraBitsPerSecond" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TeraBytes" PrefixI False) (U1 *)) (C1 * (MetaCons "TeraBytesPerSecond" PrefixI False) (U1 *)))))))

Application

data Application Source #

An application is any Amazon or third-party software that you can add to the cluster. This structure contains a list of strings that indicates the software to use with the cluster and accepts a user argument list. Amazon EMR accepts and forwards the argument list to the corresponding installation script as bootstrap action argument. For more information, see Using the MapR Distribution for Hadoop . Currently supported values are:

  • "mapr-m3" - launch the cluster using MapR M3 Edition.
  • "mapr-m5" - launch the cluster using MapR M5 Edition.
  • "mapr" with the user arguments specifying "--edition,m3" or "--edition,m5" - launch the cluster using MapR M3 or M5 Edition, respectively.

See: application smart constructor.

Instances

Eq Application Source # 
Data Application Source # 

Methods

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

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

toConstr :: Application -> Constr #

dataTypeOf :: Application -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Application Source # 
Show Application Source # 
Generic Application Source # 

Associated Types

type Rep Application :: * -> * #

Hashable Application Source # 
ToJSON Application Source # 
FromJSON Application Source # 
NFData Application Source # 

Methods

rnf :: Application -> () #

type Rep Application Source # 
type Rep Application = D1 * (MetaData "Application" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "Application'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_aArgs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_aAdditionalInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_aVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

application :: Application Source #

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

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

  • aArgs - Arguments for Amazon EMR to pass to the application.
  • aAdditionalInfo - This option is for advanced users only. This is meta information about third-party applications that third-party vendors use for testing purposes.
  • aName - The name of the application.
  • aVersion - The version of the application.

aArgs :: Lens' Application [Text] Source #

Arguments for Amazon EMR to pass to the application.

aAdditionalInfo :: Lens' Application (HashMap Text Text) Source #

This option is for advanced users only. This is meta information about third-party applications that third-party vendors use for testing purposes.

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

The name of the application.

aVersion :: Lens' Application (Maybe Text) Source #

The version of the application.

AutoScalingPolicy

data AutoScalingPolicy Source #

An automatic scaling policy for a core instance group or task instance group in an Amazon EMR cluster. An automatic scaling policy defines how an instance group dynamically adds and terminates EC2 instances in response to the value of a CloudWatch metric. See PutAutoScalingPolicy .

See: autoScalingPolicy smart constructor.

Instances

Eq AutoScalingPolicy Source # 
Data AutoScalingPolicy Source # 

Methods

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

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

toConstr :: AutoScalingPolicy -> Constr #

dataTypeOf :: AutoScalingPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: AutoScalingPolicy -> () #

type Rep AutoScalingPolicy Source # 
type Rep AutoScalingPolicy = D1 * (MetaData "AutoScalingPolicy" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "AutoScalingPolicy'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_aspConstraints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ScalingConstraints)) (S1 * (MetaSel (Just Symbol "_aspRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [ScalingRule]))))

autoScalingPolicy Source #

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

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

  • aspConstraints - The upper and lower EC2 instance limits for an automatic scaling policy. Automatic scaling activity will not cause an instance group to grow above or below these limits.
  • aspRules - The scale-in and scale-out rules that comprise the automatic scaling policy.

aspConstraints :: Lens' AutoScalingPolicy ScalingConstraints Source #

The upper and lower EC2 instance limits for an automatic scaling policy. Automatic scaling activity will not cause an instance group to grow above or below these limits.

aspRules :: Lens' AutoScalingPolicy [ScalingRule] Source #

The scale-in and scale-out rules that comprise the automatic scaling policy.

AutoScalingPolicyDescription

data AutoScalingPolicyDescription Source #

An automatic scaling policy for a core instance group or task instance group in an Amazon EMR cluster. The automatic scaling policy defines how an instance group dynamically adds and terminates EC2 instances in response to the value of a CloudWatch metric. See PutAutoScalingPolicy .

See: autoScalingPolicyDescription smart constructor.

Instances

Eq AutoScalingPolicyDescription Source # 
Data AutoScalingPolicyDescription Source # 

Methods

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

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

toConstr :: AutoScalingPolicyDescription -> Constr #

dataTypeOf :: AutoScalingPolicyDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AutoScalingPolicyDescription Source # 
Show AutoScalingPolicyDescription Source # 
Generic AutoScalingPolicyDescription Source # 
Hashable AutoScalingPolicyDescription Source # 
FromJSON AutoScalingPolicyDescription Source # 
NFData AutoScalingPolicyDescription Source # 
type Rep AutoScalingPolicyDescription Source # 
type Rep AutoScalingPolicyDescription = D1 * (MetaData "AutoScalingPolicyDescription" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "AutoScalingPolicyDescription'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_aspdStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AutoScalingPolicyStatus))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aspdRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ScalingRule]))) (S1 * (MetaSel (Just Symbol "_aspdConstraints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ScalingConstraints))))))

autoScalingPolicyDescription :: AutoScalingPolicyDescription Source #

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

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

  • aspdStatus - The status of an automatic scaling policy.
  • aspdRules - The scale-in and scale-out rules that comprise the automatic scaling policy.
  • aspdConstraints - The upper and lower EC2 instance limits for an automatic scaling policy. Automatic scaling activity will not cause an instance group to grow above or below these limits.

aspdStatus :: Lens' AutoScalingPolicyDescription (Maybe AutoScalingPolicyStatus) Source #

The status of an automatic scaling policy.

aspdRules :: Lens' AutoScalingPolicyDescription [ScalingRule] Source #

The scale-in and scale-out rules that comprise the automatic scaling policy.

aspdConstraints :: Lens' AutoScalingPolicyDescription (Maybe ScalingConstraints) Source #

The upper and lower EC2 instance limits for an automatic scaling policy. Automatic scaling activity will not cause an instance group to grow above or below these limits.

AutoScalingPolicyStateChangeReason

data AutoScalingPolicyStateChangeReason Source #

The reason for an AutoScalingPolicyStatus change.

See: autoScalingPolicyStateChangeReason smart constructor.

Instances

Eq AutoScalingPolicyStateChangeReason Source # 
Data AutoScalingPolicyStateChangeReason Source # 

Methods

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

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

toConstr :: AutoScalingPolicyStateChangeReason -> Constr #

dataTypeOf :: AutoScalingPolicyStateChangeReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AutoScalingPolicyStateChangeReason Source # 
Show AutoScalingPolicyStateChangeReason Source # 
Generic AutoScalingPolicyStateChangeReason Source # 
Hashable AutoScalingPolicyStateChangeReason Source # 
FromJSON AutoScalingPolicyStateChangeReason Source # 
NFData AutoScalingPolicyStateChangeReason Source # 
type Rep AutoScalingPolicyStateChangeReason Source # 
type Rep AutoScalingPolicyStateChangeReason = D1 * (MetaData "AutoScalingPolicyStateChangeReason" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "AutoScalingPolicyStateChangeReason'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_aspscrCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AutoScalingPolicyStateChangeReasonCode))) (S1 * (MetaSel (Just Symbol "_aspscrMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

autoScalingPolicyStateChangeReason :: AutoScalingPolicyStateChangeReason Source #

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

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

  • aspscrCode - The code indicating the reason for the change in status.USER_REQUEST indicates that the scaling policy status was changed by a user. PROVISION_FAILURE indicates that the status change was because the policy failed to provision. CLEANUP_FAILURE indicates an error.
  • aspscrMessage - A friendly, more verbose message that accompanies an automatic scaling policy state change.

aspscrCode :: Lens' AutoScalingPolicyStateChangeReason (Maybe AutoScalingPolicyStateChangeReasonCode) Source #

The code indicating the reason for the change in status.USER_REQUEST indicates that the scaling policy status was changed by a user. PROVISION_FAILURE indicates that the status change was because the policy failed to provision. CLEANUP_FAILURE indicates an error.

aspscrMessage :: Lens' AutoScalingPolicyStateChangeReason (Maybe Text) Source #

A friendly, more verbose message that accompanies an automatic scaling policy state change.

AutoScalingPolicyStatus

data AutoScalingPolicyStatus Source #

The status of an automatic scaling policy.

See: autoScalingPolicyStatus smart constructor.

Instances

Eq AutoScalingPolicyStatus Source # 
Data AutoScalingPolicyStatus Source # 

Methods

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

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

toConstr :: AutoScalingPolicyStatus -> Constr #

dataTypeOf :: AutoScalingPolicyStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: AutoScalingPolicyStatus -> () #

type Rep AutoScalingPolicyStatus Source # 
type Rep AutoScalingPolicyStatus = D1 * (MetaData "AutoScalingPolicyStatus" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "AutoScalingPolicyStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_aspsState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AutoScalingPolicyState))) (S1 * (MetaSel (Just Symbol "_aspsStateChangeReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AutoScalingPolicyStateChangeReason)))))

autoScalingPolicyStatus :: AutoScalingPolicyStatus Source #

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

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

aspsState :: Lens' AutoScalingPolicyStatus (Maybe AutoScalingPolicyState) Source #

Indicates the status of the automatic scaling policy.

BootstrapActionConfig

data BootstrapActionConfig Source #

Configuration of a bootstrap action.

See: bootstrapActionConfig smart constructor.

Instances

Eq BootstrapActionConfig Source # 
Data BootstrapActionConfig Source # 

Methods

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

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

toConstr :: BootstrapActionConfig -> Constr #

dataTypeOf :: BootstrapActionConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: BootstrapActionConfig -> () #

type Rep BootstrapActionConfig Source # 
type Rep BootstrapActionConfig = D1 * (MetaData "BootstrapActionConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "BootstrapActionConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bacName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_bacScriptBootstrapAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ScriptBootstrapActionConfig))))

bootstrapActionConfig Source #

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

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

bacName :: Lens' BootstrapActionConfig Text Source #

The name of the bootstrap action.

CancelStepsInfo

data CancelStepsInfo Source #

Specification of the status of a CancelSteps request. Available only in Amazon EMR version 4.8.0 and later, excluding version 5.0.0.

See: cancelStepsInfo smart constructor.

Instances

Eq CancelStepsInfo Source # 
Data CancelStepsInfo Source # 

Methods

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

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

toConstr :: CancelStepsInfo -> Constr #

dataTypeOf :: CancelStepsInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: CancelStepsInfo -> () #

type Rep CancelStepsInfo Source # 
type Rep CancelStepsInfo = D1 * (MetaData "CancelStepsInfo" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "CancelStepsInfo'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_csiStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe CancelStepsRequestStatus))) ((:*:) * (S1 * (MetaSel (Just Symbol "_csiStepId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_csiReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

cancelStepsInfo :: CancelStepsInfo Source #

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

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

  • csiStatus - The status of a CancelSteps Request. The value may be SUBMITTED or FAILED.
  • csiStepId - The encrypted StepId of a step.
  • csiReason - The reason for the failure if the CancelSteps request fails.

csiStatus :: Lens' CancelStepsInfo (Maybe CancelStepsRequestStatus) Source #

The status of a CancelSteps Request. The value may be SUBMITTED or FAILED.

csiStepId :: Lens' CancelStepsInfo (Maybe Text) Source #

The encrypted StepId of a step.

csiReason :: Lens' CancelStepsInfo (Maybe Text) Source #

The reason for the failure if the CancelSteps request fails.

CloudWatchAlarmDefinition

data CloudWatchAlarmDefinition Source #

The definition of a CloudWatch metric alarm, which determines when an automatic scaling activity is triggered. When the defined alarm conditions are satisfied, scaling activity begins.

See: cloudWatchAlarmDefinition smart constructor.

Instances

Eq CloudWatchAlarmDefinition Source # 
Data CloudWatchAlarmDefinition Source # 

Methods

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

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

toConstr :: CloudWatchAlarmDefinition -> Constr #

dataTypeOf :: CloudWatchAlarmDefinition -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CloudWatchAlarmDefinition Source # 
Show CloudWatchAlarmDefinition Source # 
Generic CloudWatchAlarmDefinition Source # 
Hashable CloudWatchAlarmDefinition Source # 
ToJSON CloudWatchAlarmDefinition Source # 
FromJSON CloudWatchAlarmDefinition Source # 
NFData CloudWatchAlarmDefinition Source # 
type Rep CloudWatchAlarmDefinition Source # 

cloudWatchAlarmDefinition Source #

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

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

  • cwadEvaluationPeriods - The number of periods, expressed in seconds using Period , during which the alarm condition must exist before the alarm triggers automatic scaling activity. The default value is 1 .
  • cwadNamespace - The namespace for the CloudWatch metric. The default is AWS/ElasticMapReduce .
  • cwadDimensions - A CloudWatch metric dimension.
  • cwadUnit - The unit of measure associated with the CloudWatch metric being watched. The value specified for Unit must correspond to the units specified in the CloudWatch metric.
  • cwadStatistic - The statistic to apply to the metric associated with the alarm. The default is AVERAGE .
  • cwadComparisonOperator - Determines how the metric specified by MetricName is compared to the value specified by Threshold .
  • cwadMetricName - The name of the CloudWatch metric that is watched to determine an alarm condition.
  • cwadPeriod - The period, in seconds, over which the statistic is applied. EMR CloudWatch metrics are emitted every five minutes (300 seconds), so if an EMR CloudWatch metric is specified, specify 300 .
  • cwadThreshold - The value against which the specified statistic is compared.

cwadEvaluationPeriods :: Lens' CloudWatchAlarmDefinition (Maybe Int) Source #

The number of periods, expressed in seconds using Period , during which the alarm condition must exist before the alarm triggers automatic scaling activity. The default value is 1 .

cwadNamespace :: Lens' CloudWatchAlarmDefinition (Maybe Text) Source #

The namespace for the CloudWatch metric. The default is AWS/ElasticMapReduce .

cwadUnit :: Lens' CloudWatchAlarmDefinition (Maybe Unit) Source #

The unit of measure associated with the CloudWatch metric being watched. The value specified for Unit must correspond to the units specified in the CloudWatch metric.

cwadStatistic :: Lens' CloudWatchAlarmDefinition (Maybe Statistic) Source #

The statistic to apply to the metric associated with the alarm. The default is AVERAGE .

cwadComparisonOperator :: Lens' CloudWatchAlarmDefinition ComparisonOperator Source #

Determines how the metric specified by MetricName is compared to the value specified by Threshold .

cwadMetricName :: Lens' CloudWatchAlarmDefinition Text Source #

The name of the CloudWatch metric that is watched to determine an alarm condition.

cwadPeriod :: Lens' CloudWatchAlarmDefinition Int Source #

The period, in seconds, over which the statistic is applied. EMR CloudWatch metrics are emitted every five minutes (300 seconds), so if an EMR CloudWatch metric is specified, specify 300 .

cwadThreshold :: Lens' CloudWatchAlarmDefinition Double Source #

The value against which the specified statistic is compared.

Cluster

data Cluster Source #

The detailed description of the cluster.

See: cluster smart constructor.

Instances

Eq Cluster Source # 

Methods

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

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

Data Cluster Source # 

Methods

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

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

toConstr :: Cluster -> Constr #

dataTypeOf :: Cluster -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Cluster Source # 
Show Cluster Source # 
Generic Cluster Source # 

Associated Types

type Rep Cluster :: * -> * #

Methods

from :: Cluster -> Rep Cluster x #

to :: Rep Cluster x -> Cluster #

Hashable Cluster Source # 

Methods

hashWithSalt :: Int -> Cluster -> Int #

hash :: Cluster -> Int #

FromJSON Cluster Source # 
NFData Cluster Source # 

Methods

rnf :: Cluster -> () #

type Rep Cluster Source # 
type Rep Cluster = D1 * (MetaData "Cluster" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "Cluster'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cluRequestedAMIVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluEBSRootVolumeSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_cluEC2InstanceAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe EC2InstanceAttributes))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluNormalizedInstanceHours") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Configuration]))) (S1 * (MetaSel (Just Symbol "_cluCustomAMIId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cluAutoScalingRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluSecurityConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cluScaleDownBehavior") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ScaleDownBehavior))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluInstanceCollectionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceCollectionType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluReleaseLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cluRepoUpgradeOnBoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RepoUpgradeOnBoot))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cluLogURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluKerberosAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe KerberosAttributes))) (S1 * (MetaSel (Just Symbol "_cluRunningAMIVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluMasterPublicDNSName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluTerminationProtected") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_cluVisibleToAllUsers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cluAutoTerminate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluApplications") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Application]))) (S1 * (MetaSel (Just Symbol "_cluTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Tag]))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cluServiceRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cluId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cluName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cluStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ClusterStatus))))))))

cluster Source #

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

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

  • cluRequestedAMIVersion - The AMI version requested for this cluster.
  • cluEBSRootVolumeSize - The size, in GiB, of the EBS root device volume of the Linux AMI that is used for each EC2 instance. Available in Amazon EMR version 4.x and later.
  • cluEC2InstanceAttributes - Provides information about the EC2 instances in a cluster grouped by category. For example, key name, subnet ID, IAM instance profile, and so on.
  • cluNormalizedInstanceHours - An approximation of the cost of the cluster, represented in m1.small/hours. This value is incremented one time for every hour an m1.small instance runs. Larger instances are weighted more, so an EC2 instance that is roughly four times more expensive would result in the normalized instance hours being incremented by four. This result is only an approximation and does not reflect the actual billing rate.
  • cluConfigurations - Applies only to Amazon EMR releases 4.x and later. The list of Configurations supplied to the EMR cluster.
  • cluCustomAMIId - Available only in Amazon EMR version 5.7.0 and later. The ID of a custom Amazon EBS-backed Linux AMI if the cluster uses a custom AMI.
  • cluAutoScalingRole - An IAM role for automatic scaling policies. The default role is EMR_AutoScaling_DefaultRole . The IAM role provides permissions that the automatic scaling feature requires to launch and terminate EC2 instances in an instance group.
  • cluSecurityConfiguration - The name of the security configuration applied to the cluster.
  • cluScaleDownBehavior - The way that individual Amazon EC2 instances terminate when an automatic scale-in activity occurs or an instance group is resized. TERMINATE_AT_INSTANCE_HOUR indicates that Amazon EMR terminates nodes at the instance-hour boundary, regardless of when the request to terminate the instance was submitted. This option is only available with Amazon EMR 5.1.0 and later and is the default for clusters created using that version. TERMINATE_AT_TASK_COMPLETION indicates that Amazon EMR blacklists and drains tasks from nodes before terminating the Amazon EC2 instances, regardless of the instance-hour boundary. With either behavior, Amazon EMR removes the least active nodes first and blocks instance termination if it could lead to HDFS corruption. TERMINATE_AT_TASK_COMPLETION is available only in Amazon EMR version 4.1.0 and later, and is the default for versions of Amazon EMR earlier than 5.1.0.
  • cluInstanceCollectionType - The instance group configuration of the cluster. A value of INSTANCE_GROUP indicates a uniform instance group configuration. A value of INSTANCE_FLEET indicates an instance fleets configuration.
  • cluReleaseLabel - The release label for the Amazon EMR release.
  • cluRepoUpgradeOnBoot - Applies only when CustomAmiID is used. Specifies the type of updates that are applied from the Amazon Linux AMI package repositories when an instance boots using the AMI.
  • cluLogURI - The path to the Amazon S3 location where logs for this cluster are stored.
  • cluKerberosAttributes - Attributes for Kerberos configuration when Kerberos authentication is enabled using a security configuration. For more information see Use Kerberos Authentication in the EMR Management Guide .
  • cluRunningAMIVersion - The AMI version running on this cluster.
  • cluMasterPublicDNSName - The DNS name of the master node. If the cluster is on a private subnet, this is the private DNS name. On a public subnet, this is the public DNS name.
  • cluTerminationProtected - Indicates whether Amazon EMR will lock the cluster to prevent the EC2 instances from being terminated by an API call or user intervention, or in the event of a cluster error.
  • cluVisibleToAllUsers - Indicates whether the cluster is visible to all IAM users of the AWS account associated with the cluster. If this value is set to true , all IAM users of that AWS account can view and manage the cluster if they have the proper policy permissions set. If this value is false , only the IAM user that created the cluster can view and manage it. This value can be changed using the SetVisibleToAllUsers action.
  • cluAutoTerminate - Specifies whether the cluster should terminate after completing all steps.
  • cluApplications - The applications installed on this cluster.
  • cluTags - A list of tags associated with a cluster.
  • cluServiceRole - The IAM role that will be assumed by the Amazon EMR service to access AWS resources on your behalf.
  • cluId - The unique identifier for the cluster.
  • cluName - The name of the cluster.
  • cluStatus - The current status details about the cluster.

cluRequestedAMIVersion :: Lens' Cluster (Maybe Text) Source #

The AMI version requested for this cluster.

cluEBSRootVolumeSize :: Lens' Cluster (Maybe Int) Source #

The size, in GiB, of the EBS root device volume of the Linux AMI that is used for each EC2 instance. Available in Amazon EMR version 4.x and later.

cluEC2InstanceAttributes :: Lens' Cluster (Maybe EC2InstanceAttributes) Source #

Provides information about the EC2 instances in a cluster grouped by category. For example, key name, subnet ID, IAM instance profile, and so on.

cluNormalizedInstanceHours :: Lens' Cluster (Maybe Int) Source #

An approximation of the cost of the cluster, represented in m1.small/hours. This value is incremented one time for every hour an m1.small instance runs. Larger instances are weighted more, so an EC2 instance that is roughly four times more expensive would result in the normalized instance hours being incremented by four. This result is only an approximation and does not reflect the actual billing rate.

cluConfigurations :: Lens' Cluster [Configuration] Source #

Applies only to Amazon EMR releases 4.x and later. The list of Configurations supplied to the EMR cluster.

cluCustomAMIId :: Lens' Cluster (Maybe Text) Source #

Available only in Amazon EMR version 5.7.0 and later. The ID of a custom Amazon EBS-backed Linux AMI if the cluster uses a custom AMI.

cluAutoScalingRole :: Lens' Cluster (Maybe Text) Source #

An IAM role for automatic scaling policies. The default role is EMR_AutoScaling_DefaultRole . The IAM role provides permissions that the automatic scaling feature requires to launch and terminate EC2 instances in an instance group.

cluSecurityConfiguration :: Lens' Cluster (Maybe Text) Source #

The name of the security configuration applied to the cluster.

cluScaleDownBehavior :: Lens' Cluster (Maybe ScaleDownBehavior) Source #

The way that individual Amazon EC2 instances terminate when an automatic scale-in activity occurs or an instance group is resized. TERMINATE_AT_INSTANCE_HOUR indicates that Amazon EMR terminates nodes at the instance-hour boundary, regardless of when the request to terminate the instance was submitted. This option is only available with Amazon EMR 5.1.0 and later and is the default for clusters created using that version. TERMINATE_AT_TASK_COMPLETION indicates that Amazon EMR blacklists and drains tasks from nodes before terminating the Amazon EC2 instances, regardless of the instance-hour boundary. With either behavior, Amazon EMR removes the least active nodes first and blocks instance termination if it could lead to HDFS corruption. TERMINATE_AT_TASK_COMPLETION is available only in Amazon EMR version 4.1.0 and later, and is the default for versions of Amazon EMR earlier than 5.1.0.

cluInstanceCollectionType :: Lens' Cluster (Maybe InstanceCollectionType) Source #

The instance group configuration of the cluster. A value of INSTANCE_GROUP indicates a uniform instance group configuration. A value of INSTANCE_FLEET indicates an instance fleets configuration.

cluReleaseLabel :: Lens' Cluster (Maybe Text) Source #

The release label for the Amazon EMR release.

cluRepoUpgradeOnBoot :: Lens' Cluster (Maybe RepoUpgradeOnBoot) Source #

Applies only when CustomAmiID is used. Specifies the type of updates that are applied from the Amazon Linux AMI package repositories when an instance boots using the AMI.

cluLogURI :: Lens' Cluster (Maybe Text) Source #

The path to the Amazon S3 location where logs for this cluster are stored.

cluKerberosAttributes :: Lens' Cluster (Maybe KerberosAttributes) Source #

Attributes for Kerberos configuration when Kerberos authentication is enabled using a security configuration. For more information see Use Kerberos Authentication in the EMR Management Guide .

cluRunningAMIVersion :: Lens' Cluster (Maybe Text) Source #

The AMI version running on this cluster.

cluMasterPublicDNSName :: Lens' Cluster (Maybe Text) Source #

The DNS name of the master node. If the cluster is on a private subnet, this is the private DNS name. On a public subnet, this is the public DNS name.

cluTerminationProtected :: Lens' Cluster (Maybe Bool) Source #

Indicates whether Amazon EMR will lock the cluster to prevent the EC2 instances from being terminated by an API call or user intervention, or in the event of a cluster error.

cluVisibleToAllUsers :: Lens' Cluster (Maybe Bool) Source #

Indicates whether the cluster is visible to all IAM users of the AWS account associated with the cluster. If this value is set to true , all IAM users of that AWS account can view and manage the cluster if they have the proper policy permissions set. If this value is false , only the IAM user that created the cluster can view and manage it. This value can be changed using the SetVisibleToAllUsers action.

cluAutoTerminate :: Lens' Cluster (Maybe Bool) Source #

Specifies whether the cluster should terminate after completing all steps.

cluApplications :: Lens' Cluster [Application] Source #

The applications installed on this cluster.

cluTags :: Lens' Cluster [Tag] Source #

A list of tags associated with a cluster.

cluServiceRole :: Lens' Cluster (Maybe Text) Source #

The IAM role that will be assumed by the Amazon EMR service to access AWS resources on your behalf.

cluId :: Lens' Cluster Text Source #

The unique identifier for the cluster.

cluName :: Lens' Cluster Text Source #

The name of the cluster.

cluStatus :: Lens' Cluster ClusterStatus Source #

The current status details about the cluster.

ClusterStateChangeReason

data ClusterStateChangeReason Source #

The reason that the cluster changed to its current state.

See: clusterStateChangeReason smart constructor.

Instances

Eq ClusterStateChangeReason Source # 
Data ClusterStateChangeReason Source # 

Methods

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

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

toConstr :: ClusterStateChangeReason -> Constr #

dataTypeOf :: ClusterStateChangeReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ClusterStateChangeReason Source # 
Show ClusterStateChangeReason Source # 
Generic ClusterStateChangeReason Source # 
Hashable ClusterStateChangeReason Source # 
FromJSON ClusterStateChangeReason Source # 
NFData ClusterStateChangeReason Source # 
type Rep ClusterStateChangeReason Source # 
type Rep ClusterStateChangeReason = D1 * (MetaData "ClusterStateChangeReason" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ClusterStateChangeReason'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cscrCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ClusterStateChangeReasonCode))) (S1 * (MetaSel (Just Symbol "_cscrMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

clusterStateChangeReason :: ClusterStateChangeReason Source #

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

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

  • cscrCode - The programmatic code for the state change reason.
  • cscrMessage - The descriptive message for the state change reason.

cscrCode :: Lens' ClusterStateChangeReason (Maybe ClusterStateChangeReasonCode) Source #

The programmatic code for the state change reason.

cscrMessage :: Lens' ClusterStateChangeReason (Maybe Text) Source #

The descriptive message for the state change reason.

ClusterStatus

data ClusterStatus Source #

The detailed status of the cluster.

See: clusterStatus smart constructor.

Instances

Eq ClusterStatus Source # 
Data ClusterStatus Source # 

Methods

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

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

toConstr :: ClusterStatus -> Constr #

dataTypeOf :: ClusterStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ClusterStatus Source # 
Show ClusterStatus Source # 
Generic ClusterStatus Source # 

Associated Types

type Rep ClusterStatus :: * -> * #

Hashable ClusterStatus Source # 
FromJSON ClusterStatus Source # 
NFData ClusterStatus Source # 

Methods

rnf :: ClusterStatus -> () #

type Rep ClusterStatus Source # 
type Rep ClusterStatus = D1 * (MetaData "ClusterStatus" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ClusterStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_csState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ClusterState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_csStateChangeReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ClusterStateChangeReason))) (S1 * (MetaSel (Just Symbol "_csTimeline") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ClusterTimeline))))))

clusterStatus :: ClusterStatus Source #

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

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

  • csState - The current state of the cluster.
  • csStateChangeReason - The reason for the cluster status change.
  • csTimeline - A timeline that represents the status of a cluster over the lifetime of the cluster.

csState :: Lens' ClusterStatus (Maybe ClusterState) Source #

The current state of the cluster.

csStateChangeReason :: Lens' ClusterStatus (Maybe ClusterStateChangeReason) Source #

The reason for the cluster status change.

csTimeline :: Lens' ClusterStatus (Maybe ClusterTimeline) Source #

A timeline that represents the status of a cluster over the lifetime of the cluster.

ClusterSummary

data ClusterSummary Source #

The summary description of the cluster.

See: clusterSummary smart constructor.

Instances

Eq ClusterSummary Source # 
Data ClusterSummary Source # 

Methods

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

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

toConstr :: ClusterSummary -> Constr #

dataTypeOf :: ClusterSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ClusterSummary Source # 
Show ClusterSummary Source # 
Generic ClusterSummary Source # 

Associated Types

type Rep ClusterSummary :: * -> * #

Hashable ClusterSummary Source # 
FromJSON ClusterSummary Source # 
NFData ClusterSummary Source # 

Methods

rnf :: ClusterSummary -> () #

type Rep ClusterSummary Source # 
type Rep ClusterSummary = D1 * (MetaData "ClusterSummary" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ClusterSummary'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_csStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ClusterStatus))) (S1 * (MetaSel (Just Symbol "_csNormalizedInstanceHours") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_csName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_csId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

clusterSummary :: ClusterSummary Source #

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

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

  • csStatus - The details about the current status of the cluster.
  • csNormalizedInstanceHours - An approximation of the cost of the cluster, represented in m1.small/hours. This value is incremented one time for every hour an m1.small instance runs. Larger instances are weighted more, so an EC2 instance that is roughly four times more expensive would result in the normalized instance hours being incremented by four. This result is only an approximation and does not reflect the actual billing rate.
  • csName - The name of the cluster.
  • csId - The unique identifier for the cluster.

csStatus :: Lens' ClusterSummary (Maybe ClusterStatus) Source #

The details about the current status of the cluster.

csNormalizedInstanceHours :: Lens' ClusterSummary (Maybe Int) Source #

An approximation of the cost of the cluster, represented in m1.small/hours. This value is incremented one time for every hour an m1.small instance runs. Larger instances are weighted more, so an EC2 instance that is roughly four times more expensive would result in the normalized instance hours being incremented by four. This result is only an approximation and does not reflect the actual billing rate.

csName :: Lens' ClusterSummary (Maybe Text) Source #

The name of the cluster.

csId :: Lens' ClusterSummary (Maybe Text) Source #

The unique identifier for the cluster.

ClusterTimeline

data ClusterTimeline Source #

Represents the timeline of the cluster's lifecycle.

See: clusterTimeline smart constructor.

Instances

Eq ClusterTimeline Source # 
Data ClusterTimeline Source # 

Methods

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

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

toConstr :: ClusterTimeline -> Constr #

dataTypeOf :: ClusterTimeline -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ClusterTimeline -> () #

type Rep ClusterTimeline Source # 
type Rep ClusterTimeline = D1 * (MetaData "ClusterTimeline" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ClusterTimeline'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ctReadyDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ctCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_ctEndDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))

clusterTimeline :: ClusterTimeline Source #

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

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

ctReadyDateTime :: Lens' ClusterTimeline (Maybe UTCTime) Source #

The date and time when the cluster was ready to execute steps.

ctCreationDateTime :: Lens' ClusterTimeline (Maybe UTCTime) Source #

The creation date and time of the cluster.

ctEndDateTime :: Lens' ClusterTimeline (Maybe UTCTime) Source #

The date and time when the cluster was terminated.

Command

data Command Source #

An entity describing an executable that runs on a cluster.

See: command smart constructor.

Instances

Eq Command Source # 

Methods

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

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

Data Command Source # 

Methods

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

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

toConstr :: Command -> Constr #

dataTypeOf :: Command -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Command Source # 
Show Command Source # 
Generic Command Source # 

Associated Types

type Rep Command :: * -> * #

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

Hashable Command Source # 

Methods

hashWithSalt :: Int -> Command -> Int #

hash :: Command -> Int #

FromJSON Command Source # 
NFData Command Source # 

Methods

rnf :: Command -> () #

type Rep Command Source # 
type Rep Command = D1 * (MetaData "Command" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "Command'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cArgs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cScriptPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

command :: Command Source #

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

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

  • cArgs - Arguments for Amazon EMR to pass to the command for execution.
  • cScriptPath - The Amazon S3 location of the command script.
  • cName - The name of the command.

cArgs :: Lens' Command [Text] Source #

Arguments for Amazon EMR to pass to the command for execution.

cScriptPath :: Lens' Command (Maybe Text) Source #

The Amazon S3 location of the command script.

cName :: Lens' Command (Maybe Text) Source #

The name of the command.

Configuration

data Configuration Source #

An optional configuration specification to be used when provisioning cluster instances, which can include configurations for applications and software bundled with Amazon EMR. A configuration consists of a classification, properties, and optional nested configurations. A classification refers to an application-specific configuration file. Properties are the settings you want to change in that file. For more information, see Configuring Applications .

See: configuration smart constructor.

Instances

Eq Configuration Source # 
Data Configuration Source # 

Methods

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

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

toConstr :: Configuration -> Constr #

dataTypeOf :: Configuration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Configuration Source # 
Show Configuration Source # 
Generic Configuration Source # 

Associated Types

type Rep Configuration :: * -> * #

Hashable Configuration Source # 
ToJSON Configuration Source # 
FromJSON Configuration Source # 
NFData Configuration Source # 

Methods

rnf :: Configuration -> () #

type Rep Configuration Source # 
type Rep Configuration = D1 * (MetaData "Configuration" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "Configuration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Configuration]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cClassification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))))))

configuration :: Configuration Source #

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

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

  • cConfigurations - A list of additional configurations to apply within a configuration object.
  • cClassification - The classification within a configuration.
  • cProperties - A set of properties specified within a configuration classification.

cConfigurations :: Lens' Configuration [Configuration] Source #

A list of additional configurations to apply within a configuration object.

cClassification :: Lens' Configuration (Maybe Text) Source #

The classification within a configuration.

cProperties :: Lens' Configuration (HashMap Text Text) Source #

A set of properties specified within a configuration classification.

EBSBlockDevice

data EBSBlockDevice Source #

Configuration of requested EBS block device associated with the instance group.

See: ebsBlockDevice smart constructor.

Instances

Eq EBSBlockDevice Source # 
Data EBSBlockDevice Source # 

Methods

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

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

toConstr :: EBSBlockDevice -> Constr #

dataTypeOf :: EBSBlockDevice -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EBSBlockDevice Source # 
Show EBSBlockDevice Source # 
Generic EBSBlockDevice Source # 

Associated Types

type Rep EBSBlockDevice :: * -> * #

Hashable EBSBlockDevice Source # 
FromJSON EBSBlockDevice Source # 
NFData EBSBlockDevice Source # 

Methods

rnf :: EBSBlockDevice -> () #

type Rep EBSBlockDevice Source # 
type Rep EBSBlockDevice = D1 * (MetaData "EBSBlockDevice" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "EBSBlockDevice'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ebdDevice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ebdVolumeSpecification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe VolumeSpecification)))))

ebsBlockDevice :: EBSBlockDevice Source #

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

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

  • ebdDevice - The device name that is exposed to the instance, such as devsdh.
  • ebdVolumeSpecification - EBS volume specifications such as volume type, IOPS, and size (GiB) that will be requested for the EBS volume attached to an EC2 instance in the cluster.

ebdDevice :: Lens' EBSBlockDevice (Maybe Text) Source #

The device name that is exposed to the instance, such as devsdh.

ebdVolumeSpecification :: Lens' EBSBlockDevice (Maybe VolumeSpecification) Source #

EBS volume specifications such as volume type, IOPS, and size (GiB) that will be requested for the EBS volume attached to an EC2 instance in the cluster.

EBSBlockDeviceConfig

data EBSBlockDeviceConfig Source #

Configuration of requested EBS block device associated with the instance group with count of volumes that will be associated to every instance.

See: ebsBlockDeviceConfig smart constructor.

Instances

Eq EBSBlockDeviceConfig Source # 
Data EBSBlockDeviceConfig Source # 

Methods

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

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

toConstr :: EBSBlockDeviceConfig -> Constr #

dataTypeOf :: EBSBlockDeviceConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EBSBlockDeviceConfig -> () #

type Rep EBSBlockDeviceConfig Source # 
type Rep EBSBlockDeviceConfig = D1 * (MetaData "EBSBlockDeviceConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "EBSBlockDeviceConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ebdcVolumesPerInstance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_ebdcVolumeSpecification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * VolumeSpecification))))

ebsBlockDeviceConfig Source #

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

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

  • ebdcVolumesPerInstance - Number of EBS volumes with a specific volume configuration that will be associated with every instance in the instance group
  • ebdcVolumeSpecification - EBS volume specifications such as volume type, IOPS, and size (GiB) that will be requested for the EBS volume attached to an EC2 instance in the cluster.

ebdcVolumesPerInstance :: Lens' EBSBlockDeviceConfig (Maybe Int) Source #

Number of EBS volumes with a specific volume configuration that will be associated with every instance in the instance group

ebdcVolumeSpecification :: Lens' EBSBlockDeviceConfig VolumeSpecification Source #

EBS volume specifications such as volume type, IOPS, and size (GiB) that will be requested for the EBS volume attached to an EC2 instance in the cluster.

EBSConfiguration

data EBSConfiguration Source #

The Amazon EBS configuration of a cluster instance.

See: ebsConfiguration smart constructor.

Instances

Eq EBSConfiguration Source # 
Data EBSConfiguration Source # 

Methods

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

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

toConstr :: EBSConfiguration -> Constr #

dataTypeOf :: EBSConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EBSConfiguration -> () #

type Rep EBSConfiguration Source # 
type Rep EBSConfiguration = D1 * (MetaData "EBSConfiguration" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "EBSConfiguration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ecEBSOptimized") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_ecEBSBlockDeviceConfigs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [EBSBlockDeviceConfig])))))

ebsConfiguration :: EBSConfiguration Source #

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

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

ecEBSOptimized :: Lens' EBSConfiguration (Maybe Bool) Source #

Indicates whether an Amazon EBS volume is EBS-optimized.

ecEBSBlockDeviceConfigs :: Lens' EBSConfiguration [EBSBlockDeviceConfig] Source #

An array of Amazon EBS volume specifications attached to a cluster instance.

EBSVolume

data EBSVolume Source #

EBS block device that's attached to an EC2 instance.

See: ebsVolume smart constructor.

Instances

Eq EBSVolume Source # 
Data EBSVolume Source # 

Methods

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

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

toConstr :: EBSVolume -> Constr #

dataTypeOf :: EBSVolume -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EBSVolume Source # 
Show EBSVolume Source # 
Generic EBSVolume Source # 

Associated Types

type Rep EBSVolume :: * -> * #

Hashable EBSVolume Source # 
FromJSON EBSVolume Source # 
NFData EBSVolume Source # 

Methods

rnf :: EBSVolume -> () #

type Rep EBSVolume Source # 
type Rep EBSVolume = D1 * (MetaData "EBSVolume" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "EBSVolume'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_evDevice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_evVolumeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

ebsVolume :: EBSVolume Source #

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

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

  • evDevice - The device name that is exposed to the instance, such as devsdh.
  • evVolumeId - The volume identifier of the EBS volume.

evDevice :: Lens' EBSVolume (Maybe Text) Source #

The device name that is exposed to the instance, such as devsdh.

evVolumeId :: Lens' EBSVolume (Maybe Text) Source #

The volume identifier of the EBS volume.

EC2InstanceAttributes

data EC2InstanceAttributes Source #

Provides information about the EC2 instances in a cluster grouped by category. For example, key name, subnet ID, IAM instance profile, and so on.

See: ec2InstanceAttributes smart constructor.

Instances

Eq EC2InstanceAttributes Source # 
Data EC2InstanceAttributes Source # 

Methods

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

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

toConstr :: EC2InstanceAttributes -> Constr #

dataTypeOf :: EC2InstanceAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: EC2InstanceAttributes -> () #

type Rep EC2InstanceAttributes Source # 
type Rep EC2InstanceAttributes = D1 * (MetaData "EC2InstanceAttributes" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "EC2InstanceAttributes'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_eiaEC2KeyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_eiaEmrManagedSlaveSecurityGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eiaAdditionalSlaveSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eiaRequestedEC2SubnetIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_eiaAdditionalMasterSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_eiaIAMInstanceProfile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eiaEmrManagedMasterSecurityGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_eiaEC2SubnetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eiaRequestedEC2AvailabilityZones") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eiaServiceAccessSecurityGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_eiaEC2AvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

ec2InstanceAttributes :: EC2InstanceAttributes Source #

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

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

  • eiaEC2KeyName - The name of the Amazon EC2 key pair to use when connecting with SSH into the master node as a user named "hadoop".
  • eiaEmrManagedSlaveSecurityGroup - The identifier of the Amazon EC2 security group for the slave nodes.
  • eiaAdditionalSlaveSecurityGroups - A list of additional Amazon EC2 security group IDs for the slave nodes.
  • eiaRequestedEC2SubnetIds - Applies to clusters configured with the instance fleets option. Specifies the unique identifier of one or more Amazon EC2 subnets in which to launch EC2 cluster instances. Subnets must exist within the same VPC. Amazon EMR chooses the EC2 subnet with the best fit from among the list of RequestedEc2SubnetIds , and then launches all cluster instances within that Subnet. If this value is not specified, and the account and region support EC2-Classic networks, the cluster launches instances in the EC2-Classic network and uses RequestedEc2AvailabilityZones instead of this setting. If EC2-Classic is not supported, and no Subnet is specified, Amazon EMR chooses the subnet for you. RequestedEc2SubnetIDs and RequestedEc2AvailabilityZones cannot be specified together.
  • eiaAdditionalMasterSecurityGroups - A list of additional Amazon EC2 security group IDs for the master node.
  • eiaIAMInstanceProfile - The IAM role that was specified when the cluster was launched. The EC2 instances of the cluster assume this role.
  • eiaEmrManagedMasterSecurityGroup - The identifier of the Amazon EC2 security group for the master node.
  • eiaEC2SubnetId - To launch the cluster in Amazon VPC, set this parameter to the identifier of the Amazon VPC subnet where you want the cluster to launch. If you do not specify this value, the cluster is launched in the normal AWS cloud, outside of a VPC. Amazon VPC currently does not support cluster compute quadruple extra large (cc1.4xlarge) instances. Thus, you cannot specify the cc1.4xlarge instance type for nodes of a cluster launched in a VPC.
  • eiaRequestedEC2AvailabilityZones - Applies to clusters configured with the instance fleets option. Specifies one or more Availability Zones in which to launch EC2 cluster instances when the EC2-Classic network configuration is supported. Amazon EMR chooses the Availability Zone with the best fit from among the list of RequestedEc2AvailabilityZones , and then launches all cluster instances within that Availability Zone. If you do not specify this value, Amazon EMR chooses the Availability Zone for you. RequestedEc2SubnetIDs and RequestedEc2AvailabilityZones cannot be specified together.
  • eiaServiceAccessSecurityGroup - The identifier of the Amazon EC2 security group for the Amazon EMR service to access clusters in VPC private subnets.
  • eiaEC2AvailabilityZone - The Availability Zone in which the cluster will run.

eiaEC2KeyName :: Lens' EC2InstanceAttributes (Maybe Text) Source #

The name of the Amazon EC2 key pair to use when connecting with SSH into the master node as a user named "hadoop".

eiaEmrManagedSlaveSecurityGroup :: Lens' EC2InstanceAttributes (Maybe Text) Source #

The identifier of the Amazon EC2 security group for the slave nodes.

eiaAdditionalSlaveSecurityGroups :: Lens' EC2InstanceAttributes [Text] Source #

A list of additional Amazon EC2 security group IDs for the slave nodes.

eiaRequestedEC2SubnetIds :: Lens' EC2InstanceAttributes [Text] Source #

Applies to clusters configured with the instance fleets option. Specifies the unique identifier of one or more Amazon EC2 subnets in which to launch EC2 cluster instances. Subnets must exist within the same VPC. Amazon EMR chooses the EC2 subnet with the best fit from among the list of RequestedEc2SubnetIds , and then launches all cluster instances within that Subnet. If this value is not specified, and the account and region support EC2-Classic networks, the cluster launches instances in the EC2-Classic network and uses RequestedEc2AvailabilityZones instead of this setting. If EC2-Classic is not supported, and no Subnet is specified, Amazon EMR chooses the subnet for you. RequestedEc2SubnetIDs and RequestedEc2AvailabilityZones cannot be specified together.

eiaAdditionalMasterSecurityGroups :: Lens' EC2InstanceAttributes [Text] Source #

A list of additional Amazon EC2 security group IDs for the master node.

eiaIAMInstanceProfile :: Lens' EC2InstanceAttributes (Maybe Text) Source #

The IAM role that was specified when the cluster was launched. The EC2 instances of the cluster assume this role.

eiaEmrManagedMasterSecurityGroup :: Lens' EC2InstanceAttributes (Maybe Text) Source #

The identifier of the Amazon EC2 security group for the master node.

eiaEC2SubnetId :: Lens' EC2InstanceAttributes (Maybe Text) Source #

To launch the cluster in Amazon VPC, set this parameter to the identifier of the Amazon VPC subnet where you want the cluster to launch. If you do not specify this value, the cluster is launched in the normal AWS cloud, outside of a VPC. Amazon VPC currently does not support cluster compute quadruple extra large (cc1.4xlarge) instances. Thus, you cannot specify the cc1.4xlarge instance type for nodes of a cluster launched in a VPC.

eiaRequestedEC2AvailabilityZones :: Lens' EC2InstanceAttributes [Text] Source #

Applies to clusters configured with the instance fleets option. Specifies one or more Availability Zones in which to launch EC2 cluster instances when the EC2-Classic network configuration is supported. Amazon EMR chooses the Availability Zone with the best fit from among the list of RequestedEc2AvailabilityZones , and then launches all cluster instances within that Availability Zone. If you do not specify this value, Amazon EMR chooses the Availability Zone for you. RequestedEc2SubnetIDs and RequestedEc2AvailabilityZones cannot be specified together.

eiaServiceAccessSecurityGroup :: Lens' EC2InstanceAttributes (Maybe Text) Source #

The identifier of the Amazon EC2 security group for the Amazon EMR service to access clusters in VPC private subnets.

eiaEC2AvailabilityZone :: Lens' EC2InstanceAttributes (Maybe Text) Source #

The Availability Zone in which the cluster will run.

FailureDetails

data FailureDetails Source #

The details of the step failure. The service attempts to detect the root cause for many common failures.

See: failureDetails smart constructor.

Instances

Eq FailureDetails Source # 
Data FailureDetails Source # 

Methods

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

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

toConstr :: FailureDetails -> Constr #

dataTypeOf :: FailureDetails -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FailureDetails Source # 
Show FailureDetails Source # 
Generic FailureDetails Source # 

Associated Types

type Rep FailureDetails :: * -> * #

Hashable FailureDetails Source # 
FromJSON FailureDetails Source # 
NFData FailureDetails Source # 

Methods

rnf :: FailureDetails -> () #

type Rep FailureDetails Source # 
type Rep FailureDetails = D1 * (MetaData "FailureDetails" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "FailureDetails'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_fdLogFile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fdReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_fdMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

failureDetails :: FailureDetails Source #

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

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

  • fdLogFile - The path to the log file where the step failure root cause was originally recorded.
  • fdReason - The reason for the step failure. In the case where the service cannot successfully determine the root cause of the failure, it returns "Unknown Error" as a reason.
  • fdMessage - The descriptive message including the error the EMR service has identified as the cause of step failure. This is text from an error log that describes the root cause of the failure.

fdLogFile :: Lens' FailureDetails (Maybe Text) Source #

The path to the log file where the step failure root cause was originally recorded.

fdReason :: Lens' FailureDetails (Maybe Text) Source #

The reason for the step failure. In the case where the service cannot successfully determine the root cause of the failure, it returns "Unknown Error" as a reason.

fdMessage :: Lens' FailureDetails (Maybe Text) Source #

The descriptive message including the error the EMR service has identified as the cause of step failure. This is text from an error log that describes the root cause of the failure.

HadoopJARStepConfig

data HadoopJARStepConfig Source #

A job flow step consisting of a JAR file whose main function will be executed. The main function submits a job for Hadoop to execute and waits for the job to finish or fail.

See: hadoopJARStepConfig smart constructor.

Instances

Eq HadoopJARStepConfig Source # 
Data HadoopJARStepConfig Source # 

Methods

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

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

toConstr :: HadoopJARStepConfig -> Constr #

dataTypeOf :: HadoopJARStepConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: HadoopJARStepConfig -> () #

type Rep HadoopJARStepConfig Source # 
type Rep HadoopJARStepConfig = D1 * (MetaData "HadoopJARStepConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "HadoopJARStepConfig'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_hjscArgs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_hjscMainClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_hjscProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [KeyValue]))) (S1 * (MetaSel (Just Symbol "_hjscJAR") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

hadoopJARStepConfig Source #

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

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

  • hjscArgs - A list of command line arguments passed to the JAR file's main function when executed.
  • hjscMainClass - The name of the main class in the specified Java file. If not specified, the JAR file should specify a Main-Class in its manifest file.
  • hjscProperties - A list of Java properties that are set when the step runs. You can use these properties to pass key value pairs to your main function.
  • hjscJAR - A path to a JAR file run during the step.

hjscArgs :: Lens' HadoopJARStepConfig [Text] Source #

A list of command line arguments passed to the JAR file's main function when executed.

hjscMainClass :: Lens' HadoopJARStepConfig (Maybe Text) Source #

The name of the main class in the specified Java file. If not specified, the JAR file should specify a Main-Class in its manifest file.

hjscProperties :: Lens' HadoopJARStepConfig [KeyValue] Source #

A list of Java properties that are set when the step runs. You can use these properties to pass key value pairs to your main function.

hjscJAR :: Lens' HadoopJARStepConfig Text Source #

A path to a JAR file run during the step.

HadoopStepConfig

data HadoopStepConfig Source #

A cluster step consisting of a JAR file whose main function will be executed. The main function submits a job for Hadoop to execute and waits for the job to finish or fail.

See: hadoopStepConfig smart constructor.

Instances

Eq HadoopStepConfig Source # 
Data HadoopStepConfig Source # 

Methods

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

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

toConstr :: HadoopStepConfig -> Constr #

dataTypeOf :: HadoopStepConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: HadoopStepConfig -> () #

type Rep HadoopStepConfig Source # 
type Rep HadoopStepConfig = D1 * (MetaData "HadoopStepConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "HadoopStepConfig'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_hscArgs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_hscJAR") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_hscMainClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_hscProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))))))

hadoopStepConfig :: HadoopStepConfig Source #

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

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

  • hscArgs - The list of command line arguments to pass to the JAR file's main function for execution.
  • hscJAR - The path to the JAR file that runs during the step.
  • hscMainClass - The name of the main class in the specified Java file. If not specified, the JAR file should specify a main class in its manifest file.
  • hscProperties - The list of Java properties that are set when the step runs. You can use these properties to pass key value pairs to your main function.

hscArgs :: Lens' HadoopStepConfig [Text] Source #

The list of command line arguments to pass to the JAR file's main function for execution.

hscJAR :: Lens' HadoopStepConfig (Maybe Text) Source #

The path to the JAR file that runs during the step.

hscMainClass :: Lens' HadoopStepConfig (Maybe Text) Source #

The name of the main class in the specified Java file. If not specified, the JAR file should specify a main class in its manifest file.

hscProperties :: Lens' HadoopStepConfig (HashMap Text Text) Source #

The list of Java properties that are set when the step runs. You can use these properties to pass key value pairs to your main function.

Instance

data Instance Source #

Represents an EC2 instance provisioned as part of cluster.

See: instance' smart constructor.

Instances

Eq Instance Source # 
Data Instance Source # 

Methods

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

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

toConstr :: Instance -> Constr #

dataTypeOf :: Instance -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep Instance :: * -> * #

Methods

from :: Instance -> Rep Instance x #

to :: Rep Instance x -> Instance #

Hashable Instance Source # 

Methods

hashWithSalt :: Int -> Instance -> Int #

hash :: Instance -> Int #

FromJSON Instance Source # 
NFData Instance Source # 

Methods

rnf :: Instance -> () #

type Rep Instance Source # 
type Rep Instance = D1 * (MetaData "Instance" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "Instance'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceStatus))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iPublicDNSName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iEBSVolumes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [EBSVolume]))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iEC2InstanceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iMarket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe MarketType)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iPrivateIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iInstanceFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iInstanceGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iPrivateDNSName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iPublicIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

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:

  • iStatus - The current status of the instance.
  • iPublicDNSName - The public DNS name of the instance.
  • iEBSVolumes - The list of EBS volumes that are attached to this instance.
  • iEC2InstanceId - The unique identifier of the instance in Amazon EC2.
  • iInstanceType - The EC2 instance type, for example m3.xlarge .
  • iMarket - The instance purchasing option. Valid values are ON_DEMAND or SPOT .
  • iPrivateIPAddress - The private IP address of the instance.
  • iInstanceFleetId - The unique identifier of the instance fleet to which an EC2 instance belongs.
  • iId - The unique identifier for the instance in Amazon EMR.
  • iInstanceGroupId - The identifier of the instance group to which this instance belongs.
  • iPrivateDNSName - The private DNS name of the instance.
  • iPublicIPAddress - The public IP address of the instance.

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

The current status of the instance.

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

The public DNS name of the instance.

iEBSVolumes :: Lens' Instance [EBSVolume] Source #

The list of EBS volumes that are attached to this instance.

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

The unique identifier of the instance in Amazon EC2.

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

The EC2 instance type, for example m3.xlarge .

iMarket :: Lens' Instance (Maybe MarketType) Source #

The instance purchasing option. Valid values are ON_DEMAND or SPOT .

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

The private IP address of the instance.

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

The unique identifier of the instance fleet to which an EC2 instance belongs.

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

The unique identifier for the instance in Amazon EMR.

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

The identifier of the instance group to which this instance belongs.

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

The private DNS name of the instance.

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

The public IP address of the instance.

InstanceFleet

data InstanceFleet Source #

Describes an instance fleet, which is a group of EC2 instances that host a particular node type (master, core, or task) in an Amazon EMR cluster. Instance fleets can consist of a mix of instance types and On-Demand and Spot instances, which are provisioned to meet a defined target capacity.

See: instanceFleet smart constructor.

Instances

Eq InstanceFleet Source # 
Data InstanceFleet Source # 

Methods

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

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

toConstr :: InstanceFleet -> Constr #

dataTypeOf :: InstanceFleet -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InstanceFleet Source # 
Show InstanceFleet Source # 
Generic InstanceFleet Source # 

Associated Types

type Rep InstanceFleet :: * -> * #

Hashable InstanceFleet Source # 
FromJSON InstanceFleet Source # 
NFData InstanceFleet Source # 

Methods

rnf :: InstanceFleet -> () #

type Rep InstanceFleet Source # 
type Rep InstanceFleet = D1 * (MetaData "InstanceFleet" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceFleet'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ifProvisionedSpotCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_ifStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetStatus)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifTargetOnDemandCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifInstanceFleetType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetType))) (S1 * (MetaSel (Just Symbol "_ifInstanceTypeSpecifications") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [InstanceTypeSpecification])))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ifName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ifProvisionedOnDemandCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifTargetSpotCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ifLaunchSpecifications") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetProvisioningSpecifications))))))))

instanceFleet :: InstanceFleet Source #

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

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

  • ifProvisionedSpotCapacity - The number of Spot units that have been provisioned for this instance fleet to fulfill TargetSpotCapacity . This provisioned capacity might be less than or greater than TargetSpotCapacity .
  • ifStatus - The current status of the instance fleet.
  • ifTargetOnDemandCapacity - The target capacity of On-Demand units for the instance fleet, which determines how many On-Demand instances to provision. When the instance fleet launches, Amazon EMR tries to provision On-Demand instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When an On-Demand instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units. You can use 'InstanceFleet$ProvisionedOnDemandCapacity' to determine the Spot capacity units that have been provisioned for the instance fleet.
  • ifInstanceFleetType - The node type that the instance fleet hosts. Valid values are MASTER, CORE, or TASK.
  • ifInstanceTypeSpecifications - The specification for the instance types that comprise an instance fleet. Up to five unique instance specifications may be defined for each instance fleet.
  • ifName - A friendly name for the instance fleet.
  • ifProvisionedOnDemandCapacity - The number of On-Demand units that have been provisioned for the instance fleet to fulfill TargetOnDemandCapacity . This provisioned capacity might be less than or greater than TargetOnDemandCapacity .
  • ifTargetSpotCapacity - The target capacity of Spot units for the instance fleet, which determines how many Spot instances to provision. When the instance fleet launches, Amazon EMR tries to provision Spot instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When a Spot instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units. You can use 'InstanceFleet$ProvisionedSpotCapacity' to determine the Spot capacity units that have been provisioned for the instance fleet.
  • ifId - The unique identifier of the instance fleet.
  • ifLaunchSpecifications - Describes the launch specification for an instance fleet.

ifProvisionedSpotCapacity :: Lens' InstanceFleet (Maybe Natural) Source #

The number of Spot units that have been provisioned for this instance fleet to fulfill TargetSpotCapacity . This provisioned capacity might be less than or greater than TargetSpotCapacity .

ifStatus :: Lens' InstanceFleet (Maybe InstanceFleetStatus) Source #

The current status of the instance fleet.

ifTargetOnDemandCapacity :: Lens' InstanceFleet (Maybe Natural) Source #

The target capacity of On-Demand units for the instance fleet, which determines how many On-Demand instances to provision. When the instance fleet launches, Amazon EMR tries to provision On-Demand instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When an On-Demand instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units. You can use 'InstanceFleet$ProvisionedOnDemandCapacity' to determine the Spot capacity units that have been provisioned for the instance fleet.

ifInstanceFleetType :: Lens' InstanceFleet (Maybe InstanceFleetType) Source #

The node type that the instance fleet hosts. Valid values are MASTER, CORE, or TASK.

ifInstanceTypeSpecifications :: Lens' InstanceFleet [InstanceTypeSpecification] Source #

The specification for the instance types that comprise an instance fleet. Up to five unique instance specifications may be defined for each instance fleet.

ifName :: Lens' InstanceFleet (Maybe Text) Source #

A friendly name for the instance fleet.

ifProvisionedOnDemandCapacity :: Lens' InstanceFleet (Maybe Natural) Source #

The number of On-Demand units that have been provisioned for the instance fleet to fulfill TargetOnDemandCapacity . This provisioned capacity might be less than or greater than TargetOnDemandCapacity .

ifTargetSpotCapacity :: Lens' InstanceFleet (Maybe Natural) Source #

The target capacity of Spot units for the instance fleet, which determines how many Spot instances to provision. When the instance fleet launches, Amazon EMR tries to provision Spot instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When a Spot instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units. You can use 'InstanceFleet$ProvisionedSpotCapacity' to determine the Spot capacity units that have been provisioned for the instance fleet.

ifId :: Lens' InstanceFleet (Maybe Text) Source #

The unique identifier of the instance fleet.

ifLaunchSpecifications :: Lens' InstanceFleet (Maybe InstanceFleetProvisioningSpecifications) Source #

Describes the launch specification for an instance fleet.

InstanceFleetConfig

data InstanceFleetConfig Source #

The configuration that defines an instance fleet.

See: instanceFleetConfig smart constructor.

Instances

Eq InstanceFleetConfig Source # 
Data InstanceFleetConfig Source # 

Methods

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

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

toConstr :: InstanceFleetConfig -> Constr #

dataTypeOf :: InstanceFleetConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceFleetConfig -> () #

type Rep InstanceFleetConfig Source # 
type Rep InstanceFleetConfig = D1 * (MetaData "InstanceFleetConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceFleetConfig'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ifcInstanceTypeConfigs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [InstanceTypeConfig]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifcTargetOnDemandCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_ifcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifcTargetSpotCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifcLaunchSpecifications") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetProvisioningSpecifications))) (S1 * (MetaSel (Just Symbol "_ifcInstanceFleetType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InstanceFleetType))))))

instanceFleetConfig Source #

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

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

  • ifcInstanceTypeConfigs - The instance type configurations that define the EC2 instances in the instance fleet.
  • ifcTargetOnDemandCapacity - The target capacity of On-Demand units for the instance fleet, which determines how many On-Demand instances to provision. When the instance fleet launches, Amazon EMR tries to provision On-Demand instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When an On-Demand instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units.
  • ifcName - The friendly name of the instance fleet.
  • ifcTargetSpotCapacity - The target capacity of Spot units for the instance fleet, which determines how many Spot instances to provision. When the instance fleet launches, Amazon EMR tries to provision Spot instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When a Spot instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units.
  • ifcLaunchSpecifications - The launch specification for the instance fleet.
  • ifcInstanceFleetType - The node type that the instance fleet hosts. Valid values are MASTER,CORE,and TASK.

ifcInstanceTypeConfigs :: Lens' InstanceFleetConfig [InstanceTypeConfig] Source #

The instance type configurations that define the EC2 instances in the instance fleet.

ifcTargetOnDemandCapacity :: Lens' InstanceFleetConfig (Maybe Natural) Source #

The target capacity of On-Demand units for the instance fleet, which determines how many On-Demand instances to provision. When the instance fleet launches, Amazon EMR tries to provision On-Demand instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When an On-Demand instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units.

ifcName :: Lens' InstanceFleetConfig (Maybe Text) Source #

The friendly name of the instance fleet.

ifcTargetSpotCapacity :: Lens' InstanceFleetConfig (Maybe Natural) Source #

The target capacity of Spot units for the instance fleet, which determines how many Spot instances to provision. When the instance fleet launches, Amazon EMR tries to provision Spot instances as specified by InstanceTypeConfig . Each instance configuration has a specified WeightedCapacity . When a Spot instance is provisioned, the WeightedCapacity units count toward the target capacity. Amazon EMR provisions instances until the target capacity is totally fulfilled, even if this results in an overage. For example, if there are 2 units remaining to fulfill capacity, and Amazon EMR can only provision an instance with a WeightedCapacity of 5 units, the instance is provisioned, and the target capacity is exceeded by 3 units.

ifcInstanceFleetType :: Lens' InstanceFleetConfig InstanceFleetType Source #

The node type that the instance fleet hosts. Valid values are MASTER,CORE,and TASK.

InstanceFleetModifyConfig

data InstanceFleetModifyConfig Source #

Configuration parameters for an instance fleet modification request.

See: instanceFleetModifyConfig smart constructor.

Instances

Eq InstanceFleetModifyConfig Source # 
Data InstanceFleetModifyConfig Source # 

Methods

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

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

toConstr :: InstanceFleetModifyConfig -> Constr #

dataTypeOf :: InstanceFleetModifyConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InstanceFleetModifyConfig Source # 
Show InstanceFleetModifyConfig Source # 
Generic InstanceFleetModifyConfig Source # 
Hashable InstanceFleetModifyConfig Source # 
ToJSON InstanceFleetModifyConfig Source # 
NFData InstanceFleetModifyConfig Source # 
type Rep InstanceFleetModifyConfig Source # 
type Rep InstanceFleetModifyConfig = D1 * (MetaData "InstanceFleetModifyConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceFleetModifyConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifmcTargetOnDemandCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifmcTargetSpotCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_ifmcInstanceFleetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

instanceFleetModifyConfig Source #

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

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

  • ifmcTargetOnDemandCapacity - The target capacity of On-Demand units for the instance fleet. For more information see 'InstanceFleetConfig$TargetOnDemandCapacity' .
  • ifmcTargetSpotCapacity - The target capacity of Spot units for the instance fleet. For more information, see 'InstanceFleetConfig$TargetSpotCapacity' .
  • ifmcInstanceFleetId - A unique identifier for the instance fleet.

ifmcTargetOnDemandCapacity :: Lens' InstanceFleetModifyConfig (Maybe Natural) Source #

The target capacity of On-Demand units for the instance fleet. For more information see 'InstanceFleetConfig$TargetOnDemandCapacity' .

ifmcTargetSpotCapacity :: Lens' InstanceFleetModifyConfig (Maybe Natural) Source #

The target capacity of Spot units for the instance fleet. For more information, see 'InstanceFleetConfig$TargetSpotCapacity' .

ifmcInstanceFleetId :: Lens' InstanceFleetModifyConfig Text Source #

A unique identifier for the instance fleet.

InstanceFleetProvisioningSpecifications

data InstanceFleetProvisioningSpecifications Source #

The launch specification for Spot instances in the fleet, which determines the defined duration and provisioning timeout behavior.

See: instanceFleetProvisioningSpecifications smart constructor.

Instances

Eq InstanceFleetProvisioningSpecifications Source # 
Data InstanceFleetProvisioningSpecifications Source # 

Methods

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

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

toConstr :: InstanceFleetProvisioningSpecifications -> Constr #

dataTypeOf :: InstanceFleetProvisioningSpecifications -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InstanceFleetProvisioningSpecifications Source # 
Show InstanceFleetProvisioningSpecifications Source # 
Generic InstanceFleetProvisioningSpecifications Source # 
Hashable InstanceFleetProvisioningSpecifications Source # 
ToJSON InstanceFleetProvisioningSpecifications Source # 
FromJSON InstanceFleetProvisioningSpecifications Source # 
NFData InstanceFleetProvisioningSpecifications Source # 
type Rep InstanceFleetProvisioningSpecifications Source # 
type Rep InstanceFleetProvisioningSpecifications = D1 * (MetaData "InstanceFleetProvisioningSpecifications" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" True) (C1 * (MetaCons "InstanceFleetProvisioningSpecifications'" PrefixI True) (S1 * (MetaSel (Just Symbol "_ifpsSpotSpecification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SpotProvisioningSpecification)))

instanceFleetProvisioningSpecifications Source #

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

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

  • ifpsSpotSpecification - The launch specification for Spot instances in the fleet, which determines the defined duration and provisioning timeout behavior.

ifpsSpotSpecification :: Lens' InstanceFleetProvisioningSpecifications SpotProvisioningSpecification Source #

The launch specification for Spot instances in the fleet, which determines the defined duration and provisioning timeout behavior.

InstanceFleetStateChangeReason

data InstanceFleetStateChangeReason Source #

Provides status change reason details for the instance fleet.

See: instanceFleetStateChangeReason smart constructor.

Instances

Eq InstanceFleetStateChangeReason Source # 
Data InstanceFleetStateChangeReason Source # 

Methods

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

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

toConstr :: InstanceFleetStateChangeReason -> Constr #

dataTypeOf :: InstanceFleetStateChangeReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InstanceFleetStateChangeReason Source # 
Show InstanceFleetStateChangeReason Source # 
Generic InstanceFleetStateChangeReason Source # 
Hashable InstanceFleetStateChangeReason Source # 
FromJSON InstanceFleetStateChangeReason Source # 
NFData InstanceFleetStateChangeReason Source # 
type Rep InstanceFleetStateChangeReason Source # 
type Rep InstanceFleetStateChangeReason = D1 * (MetaData "InstanceFleetStateChangeReason" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceFleetStateChangeReason'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifscrCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetStateChangeReasonCode))) (S1 * (MetaSel (Just Symbol "_ifscrMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

instanceFleetStateChangeReason :: InstanceFleetStateChangeReason Source #

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

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

  • ifscrCode - A code corresponding to the reason the state change occurred.
  • ifscrMessage - An explanatory message.

ifscrCode :: Lens' InstanceFleetStateChangeReason (Maybe InstanceFleetStateChangeReasonCode) Source #

A code corresponding to the reason the state change occurred.

InstanceFleetStatus

data InstanceFleetStatus Source #

The status of the instance fleet.

See: instanceFleetStatus smart constructor.

Instances

Eq InstanceFleetStatus Source # 
Data InstanceFleetStatus Source # 

Methods

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

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

toConstr :: InstanceFleetStatus -> Constr #

dataTypeOf :: InstanceFleetStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceFleetStatus -> () #

type Rep InstanceFleetStatus Source # 
type Rep InstanceFleetStatus = D1 * (MetaData "InstanceFleetStatus" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceFleetStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifsState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ifsStateChangeReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetStateChangeReason))) (S1 * (MetaSel (Just Symbol "_ifsTimeline") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceFleetTimeline))))))

instanceFleetStatus :: InstanceFleetStatus Source #

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

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

  • ifsState - A code representing the instance fleet status. * PROVISIONING —The instance fleet is provisioning EC2 resources and is not yet ready to run jobs. * BOOTSTRAPPING —EC2 instances and other resources have been provisioned and the bootstrap actions specified for the instances are underway. * RUNNING —EC2 instances and other resources are running. They are either executing jobs or waiting to execute jobs. * RESIZING —A resize operation is underway. EC2 instances are either being added or removed. * SUSPENDED —A resize operation could not complete. Existing EC2 instances are running, but instances can't be added or removed. * TERMINATING —The instance fleet is terminating EC2 instances. * TERMINATED —The instance fleet is no longer active, and all EC2 instances have been terminated.
  • ifsStateChangeReason - Provides status change reason details for the instance fleet.
  • ifsTimeline - Provides historical timestamps for the instance fleet, including the time of creation, the time it became ready to run jobs, and the time of termination.

ifsState :: Lens' InstanceFleetStatus (Maybe InstanceFleetState) Source #

A code representing the instance fleet status. * PROVISIONING —The instance fleet is provisioning EC2 resources and is not yet ready to run jobs. * BOOTSTRAPPING —EC2 instances and other resources have been provisioned and the bootstrap actions specified for the instances are underway. * RUNNING —EC2 instances and other resources are running. They are either executing jobs or waiting to execute jobs. * RESIZING —A resize operation is underway. EC2 instances are either being added or removed. * SUSPENDED —A resize operation could not complete. Existing EC2 instances are running, but instances can't be added or removed. * TERMINATING —The instance fleet is terminating EC2 instances. * TERMINATED —The instance fleet is no longer active, and all EC2 instances have been terminated.

ifsStateChangeReason :: Lens' InstanceFleetStatus (Maybe InstanceFleetStateChangeReason) Source #

Provides status change reason details for the instance fleet.

ifsTimeline :: Lens' InstanceFleetStatus (Maybe InstanceFleetTimeline) Source #

Provides historical timestamps for the instance fleet, including the time of creation, the time it became ready to run jobs, and the time of termination.

InstanceFleetTimeline

data InstanceFleetTimeline Source #

Provides historical timestamps for the instance fleet, including the time of creation, the time it became ready to run jobs, and the time of termination.

See: instanceFleetTimeline smart constructor.

Instances

Eq InstanceFleetTimeline Source # 
Data InstanceFleetTimeline Source # 

Methods

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

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

toConstr :: InstanceFleetTimeline -> Constr #

dataTypeOf :: InstanceFleetTimeline -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: InstanceFleetTimeline -> () #

type Rep InstanceFleetTimeline Source # 
type Rep InstanceFleetTimeline = D1 * (MetaData "InstanceFleetTimeline" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceFleetTimeline'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_iftReadyDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iftCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_iftEndDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))

instanceFleetTimeline :: InstanceFleetTimeline Source #

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

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

iftReadyDateTime :: Lens' InstanceFleetTimeline (Maybe UTCTime) Source #

The time and date the instance fleet was ready to run jobs.

iftCreationDateTime :: Lens' InstanceFleetTimeline (Maybe UTCTime) Source #

The time and date the instance fleet was created.

iftEndDateTime :: Lens' InstanceFleetTimeline (Maybe UTCTime) Source #

The time and date the instance fleet terminated.

InstanceGroup

data InstanceGroup Source #

This entity represents an instance group, which is a group of instances that have common purpose. For example, CORE instance group is used for HDFS.

See: instanceGroup smart constructor.

Instances

Eq InstanceGroup Source # 
Data InstanceGroup Source # 

Methods

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

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

toConstr :: InstanceGroup -> Constr #

dataTypeOf :: InstanceGroup -> DataType #

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

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

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

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

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

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceGroup -> m InstanceGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroup -> m InstanceGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroup -> m InstanceGroup #

Read InstanceGroup Source # 
Show InstanceGroup Source # 
Generic InstanceGroup Source # 

Associated Types

type Rep InstanceGroup :: * -> * #

Hashable InstanceGroup Source # 
FromJSON InstanceGroup Source # 
NFData InstanceGroup Source # 

Methods

rnf :: InstanceGroup -> () #

type Rep InstanceGroup Source # 
type Rep InstanceGroup = D1 * (MetaData "InstanceGroup" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceGroup'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_igStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceGroupStatus))) ((:*:) * (S1 * (MetaSel (Just Symbol "_igBidPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_igRequestedInstanceCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_igRunningInstanceCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_igConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Configuration])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_igInstanceGroupType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceGroupType))) (S1 * (MetaSel (Just Symbol "_igEBSBlockDevices") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [EBSBlockDevice])))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_igInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_igEBSOptimized") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_igMarket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe MarketType))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_igName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_igAutoScalingPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AutoScalingPolicyDescription)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_igShrinkPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ShrinkPolicy))) (S1 * (MetaSel (Just Symbol "_igId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

instanceGroup :: InstanceGroup Source #

Creates a value of InstanceGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • igStatus - The current status of the instance group.
  • igBidPrice - The bid price for each EC2 instance in the instance group when launching nodes as Spot Instances, expressed in USD.
  • igRequestedInstanceCount - The target number of instances for the instance group.
  • igRunningInstanceCount - The number of instances currently running in this instance group.
  • igConfigurations - The list of configurations supplied for an EMR cluster instance group. You can specify a separate configuration for each instance group (master, core, and task).
  • igInstanceGroupType - The type of the instance group. Valid values are MASTER, CORE or TASK.
  • igEBSBlockDevices - The EBS block devices that are mapped to this instance group.
  • igInstanceType - The EC2 instance type for all instances in the instance group.
  • igEBSOptimized - If the instance group is EBS-optimized. An Amazon EBS-optimized instance uses an optimized configuration stack and provides additional, dedicated capacity for Amazon EBS I/O.
  • igMarket - The marketplace to provision instances for this group. Valid values are ON_DEMAND or SPOT.
  • igName - The name of the instance group.
  • igAutoScalingPolicy - An automatic scaling policy for a core instance group or task instance group in an Amazon EMR cluster. The automatic scaling policy defines how an instance group dynamically adds and terminates EC2 instances in response to the value of a CloudWatch metric. See PutAutoScalingPolicy.
  • igShrinkPolicy - Policy for customizing shrink operations.
  • igId - The identifier of the instance group.

igStatus :: Lens' InstanceGroup (Maybe InstanceGroupStatus) Source #

The current status of the instance group.

igBidPrice :: Lens' InstanceGroup (Maybe Text) Source #

The bid price for each EC2 instance in the instance group when launching nodes as Spot Instances, expressed in USD.

igRequestedInstanceCount :: Lens' InstanceGroup (Maybe Int) Source #

The target number of instances for the instance group.

igRunningInstanceCount :: Lens' InstanceGroup (Maybe Int) Source #

The number of instances currently running in this instance group.

igConfigurations :: Lens' InstanceGroup [Configuration] Source #

The list of configurations supplied for an EMR cluster instance group. You can specify a separate configuration for each instance group (master, core, and task).

igInstanceGroupType :: Lens' InstanceGroup (Maybe InstanceGroupType) Source #

The type of the instance group. Valid values are MASTER, CORE or TASK.

igEBSBlockDevices :: Lens' InstanceGroup [EBSBlockDevice] Source #

The EBS block devices that are mapped to this instance group.

igInstanceType :: Lens' InstanceGroup (Maybe Text) Source #

The EC2 instance type for all instances in the instance group.

igEBSOptimized :: Lens' InstanceGroup (Maybe Bool) Source #

If the instance group is EBS-optimized. An Amazon EBS-optimized instance uses an optimized configuration stack and provides additional, dedicated capacity for Amazon EBS I/O.

igMarket :: Lens' InstanceGroup (Maybe MarketType) Source #

The marketplace to provision instances for this group. Valid values are ON_DEMAND or SPOT.

igName :: Lens' InstanceGroup (Maybe Text) Source #

The name of the instance group.

igAutoScalingPolicy :: Lens' InstanceGroup (Maybe AutoScalingPolicyDescription) Source #

An automatic scaling policy for a core instance group or task instance group in an Amazon EMR cluster. The automatic scaling policy defines how an instance group dynamically adds and terminates EC2 instances in response to the value of a CloudWatch metric. See PutAutoScalingPolicy.

igShrinkPolicy :: Lens' InstanceGroup (Maybe ShrinkPolicy) Source #

Policy for customizing shrink operations.

igId :: Lens' InstanceGroup (Maybe Text) Source #

The identifier of the instance group.

InstanceGroupConfig

data InstanceGroupConfig Source #

Configuration defining a new instance group.

See: instanceGroupConfig smart constructor.

Instances

Eq InstanceGroupConfig Source # 
Data InstanceGroupConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceGroupConfig -> c InstanceGroupConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceGroupConfig #

toConstr :: InstanceGroupConfig -> Constr #

dataTypeOf :: InstanceGroupConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceGroupConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceGroupConfig) #

gmapT :: (forall b. Data b => b -> b) -> InstanceGroupConfig -> InstanceGroupConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceGroupConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceGroupConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceGroupConfig -> m InstanceGroupConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupConfig -> m InstanceGroupConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupConfig -> m InstanceGroupConfig #

Read InstanceGroupConfig Source # 
Show InstanceGroupConfig Source # 
Generic InstanceGroupConfig Source # 
Hashable InstanceGroupConfig Source # 
ToJSON InstanceGroupConfig Source # 
NFData InstanceGroupConfig Source # 

Methods

rnf :: InstanceGroupConfig -> () #

type Rep InstanceGroupConfig Source # 

instanceGroupConfig Source #

Creates a value of InstanceGroupConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • igcEBSConfiguration - EBS configurations that will be attached to each EC2 instance in the instance group.
  • igcBidPrice - Bid price for each EC2 instance in the instance group when launching nodes as Spot Instances, expressed in USD.
  • igcConfigurations - The list of configurations supplied for an EMR cluster instance group. You can specify a separate configuration for each instance group (master, core, and task).
  • igcMarket - Market type of the EC2 instances used to create a cluster node.
  • igcName - Friendly name given to the instance group.
  • igcAutoScalingPolicy - An automatic scaling policy for a core instance group or task instance group in an Amazon EMR cluster. The automatic scaling policy defines how an instance group dynamically adds and terminates EC2 instances in response to the value of a CloudWatch metric. See PutAutoScalingPolicy .
  • igcInstanceRole - The role of the instance group in the cluster.
  • igcInstanceType - The EC2 instance type for all instances in the instance group.
  • igcInstanceCount - Target number of instances for the instance group.

igcEBSConfiguration :: Lens' InstanceGroupConfig (Maybe EBSConfiguration) Source #

EBS configurations that will be attached to each EC2 instance in the instance group.

igcBidPrice :: Lens' InstanceGroupConfig (Maybe Text) Source #

Bid price for each EC2 instance in the instance group when launching nodes as Spot Instances, expressed in USD.

igcConfigurations :: Lens' InstanceGroupConfig [Configuration] Source #

The list of configurations supplied for an EMR cluster instance group. You can specify a separate configuration for each instance group (master, core, and task).

igcMarket :: Lens' InstanceGroupConfig (Maybe MarketType) Source #

Market type of the EC2 instances used to create a cluster node.

igcName :: Lens' InstanceGroupConfig (Maybe Text) Source #

Friendly name given to the instance group.

igcAutoScalingPolicy :: Lens' InstanceGroupConfig (Maybe AutoScalingPolicy) Source #

An automatic scaling policy for a core instance group or task instance group in an Amazon EMR cluster. The automatic scaling policy defines how an instance group dynamically adds and terminates EC2 instances in response to the value of a CloudWatch metric. See PutAutoScalingPolicy .

igcInstanceRole :: Lens' InstanceGroupConfig InstanceRoleType Source #

The role of the instance group in the cluster.

igcInstanceType :: Lens' InstanceGroupConfig Text Source #

The EC2 instance type for all instances in the instance group.

igcInstanceCount :: Lens' InstanceGroupConfig Int Source #

Target number of instances for the instance group.

InstanceGroupModifyConfig

data InstanceGroupModifyConfig Source #

Modify an instance group size.

See: instanceGroupModifyConfig smart constructor.

Instances

Eq InstanceGroupModifyConfig Source # 
Data InstanceGroupModifyConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceGroupModifyConfig -> c InstanceGroupModifyConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceGroupModifyConfig #

toConstr :: InstanceGroupModifyConfig -> Constr #

dataTypeOf :: InstanceGroupModifyConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceGroupModifyConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceGroupModifyConfig) #

gmapT :: (forall b. Data b => b -> b) -> InstanceGroupModifyConfig -> InstanceGroupModifyConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupModifyConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupModifyConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceGroupModifyConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceGroupModifyConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceGroupModifyConfig -> m InstanceGroupModifyConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupModifyConfig -> m InstanceGroupModifyConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupModifyConfig -> m InstanceGroupModifyConfig #

Read InstanceGroupModifyConfig Source # 
Show InstanceGroupModifyConfig Source # 
Generic InstanceGroupModifyConfig Source # 
Hashable InstanceGroupModifyConfig Source # 
ToJSON InstanceGroupModifyConfig Source # 
NFData InstanceGroupModifyConfig Source # 
type Rep InstanceGroupModifyConfig Source # 
type Rep InstanceGroupModifyConfig = D1 * (MetaData "InstanceGroupModifyConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceGroupModifyConfig'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_igmcInstanceCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_igmcEC2InstanceIdsToTerminate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_igmcShrinkPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ShrinkPolicy))) (S1 * (MetaSel (Just Symbol "_igmcInstanceGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

instanceGroupModifyConfig Source #

Creates a value of InstanceGroupModifyConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

igmcInstanceCount :: Lens' InstanceGroupModifyConfig (Maybe Int) Source #

Target size for the instance group.

igmcEC2InstanceIdsToTerminate :: Lens' InstanceGroupModifyConfig [Text] Source #

The EC2 InstanceIds to terminate. After you terminate the instances, the instance group will not return to its original requested size.

igmcShrinkPolicy :: Lens' InstanceGroupModifyConfig (Maybe ShrinkPolicy) Source #

Policy for customizing shrink operations.

igmcInstanceGroupId :: Lens' InstanceGroupModifyConfig Text Source #

Unique ID of the instance group to expand or shrink.

InstanceGroupStateChangeReason

data InstanceGroupStateChangeReason Source #

The status change reason details for the instance group.

See: instanceGroupStateChangeReason smart constructor.

Instances

Eq InstanceGroupStateChangeReason Source # 
Data InstanceGroupStateChangeReason Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceGroupStateChangeReason -> c InstanceGroupStateChangeReason #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceGroupStateChangeReason #

toConstr :: InstanceGroupStateChangeReason -> Constr #

dataTypeOf :: InstanceGroupStateChangeReason -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceGroupStateChangeReason) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceGroupStateChangeReason) #

gmapT :: (forall b. Data b => b -> b) -> InstanceGroupStateChangeReason -> InstanceGroupStateChangeReason #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupStateChangeReason -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupStateChangeReason -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceGroupStateChangeReason -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceGroupStateChangeReason -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceGroupStateChangeReason -> m InstanceGroupStateChangeReason #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupStateChangeReason -> m InstanceGroupStateChangeReason #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupStateChangeReason -> m InstanceGroupStateChangeReason #

Read InstanceGroupStateChangeReason Source # 
Show InstanceGroupStateChangeReason Source # 
Generic InstanceGroupStateChangeReason Source # 
Hashable InstanceGroupStateChangeReason Source # 
FromJSON InstanceGroupStateChangeReason Source # 
NFData InstanceGroupStateChangeReason Source # 
type Rep InstanceGroupStateChangeReason Source # 
type Rep InstanceGroupStateChangeReason = D1 * (MetaData "InstanceGroupStateChangeReason" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceGroupStateChangeReason'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_igscrCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceGroupStateChangeReasonCode))) (S1 * (MetaSel (Just Symbol "_igscrMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

instanceGroupStateChangeReason :: InstanceGroupStateChangeReason Source #

Creates a value of InstanceGroupStateChangeReason with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • igscrCode - The programmable code for the state change reason.
  • igscrMessage - The status change reason description.

igscrCode :: Lens' InstanceGroupStateChangeReason (Maybe InstanceGroupStateChangeReasonCode) Source #

The programmable code for the state change reason.

igscrMessage :: Lens' InstanceGroupStateChangeReason (Maybe Text) Source #

The status change reason description.

InstanceGroupStatus

data InstanceGroupStatus Source #

The details of the instance group status.

See: instanceGroupStatus smart constructor.

Instances

Eq InstanceGroupStatus Source # 
Data InstanceGroupStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceGroupStatus -> c InstanceGroupStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceGroupStatus #

toConstr :: InstanceGroupStatus -> Constr #

dataTypeOf :: InstanceGroupStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceGroupStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceGroupStatus) #

gmapT :: (forall b. Data b => b -> b) -> InstanceGroupStatus -> InstanceGroupStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceGroupStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceGroupStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceGroupStatus -> m InstanceGroupStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupStatus -> m InstanceGroupStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupStatus -> m InstanceGroupStatus #

Read InstanceGroupStatus Source # 
Show InstanceGroupStatus Source # 
Generic InstanceGroupStatus Source # 
Hashable InstanceGroupStatus Source # 
FromJSON InstanceGroupStatus Source # 
NFData InstanceGroupStatus Source # 

Methods

rnf :: InstanceGroupStatus -> () #

type Rep InstanceGroupStatus Source # 
type Rep InstanceGroupStatus = D1 * (MetaData "InstanceGroupStatus" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceGroupStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_igsState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceGroupState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_igsStateChangeReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceGroupStateChangeReason))) (S1 * (MetaSel (Just Symbol "_igsTimeline") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceGroupTimeline))))))

instanceGroupStatus :: InstanceGroupStatus Source #

Creates a value of InstanceGroupStatus with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • igsState - The current state of the instance group.
  • igsStateChangeReason - The status change reason details for the instance group.
  • igsTimeline - The timeline of the instance group status over time.

igsState :: Lens' InstanceGroupStatus (Maybe InstanceGroupState) Source #

The current state of the instance group.

igsStateChangeReason :: Lens' InstanceGroupStatus (Maybe InstanceGroupStateChangeReason) Source #

The status change reason details for the instance group.

igsTimeline :: Lens' InstanceGroupStatus (Maybe InstanceGroupTimeline) Source #

The timeline of the instance group status over time.

InstanceGroupTimeline

data InstanceGroupTimeline Source #

The timeline of the instance group lifecycle.

See: instanceGroupTimeline smart constructor.

Instances

Eq InstanceGroupTimeline Source # 
Data InstanceGroupTimeline Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceGroupTimeline -> c InstanceGroupTimeline #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceGroupTimeline #

toConstr :: InstanceGroupTimeline -> Constr #

dataTypeOf :: InstanceGroupTimeline -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceGroupTimeline) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceGroupTimeline) #

gmapT :: (forall b. Data b => b -> b) -> InstanceGroupTimeline -> InstanceGroupTimeline #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupTimeline -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceGroupTimeline -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceGroupTimeline -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceGroupTimeline -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceGroupTimeline -> m InstanceGroupTimeline #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupTimeline -> m InstanceGroupTimeline #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceGroupTimeline -> m InstanceGroupTimeline #

Read InstanceGroupTimeline Source # 
Show InstanceGroupTimeline Source # 
Generic InstanceGroupTimeline Source # 
Hashable InstanceGroupTimeline Source # 
FromJSON InstanceGroupTimeline Source # 
NFData InstanceGroupTimeline Source # 

Methods

rnf :: InstanceGroupTimeline -> () #

type Rep InstanceGroupTimeline Source # 
type Rep InstanceGroupTimeline = D1 * (MetaData "InstanceGroupTimeline" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceGroupTimeline'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_igtReadyDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_igtCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_igtEndDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))

instanceGroupTimeline :: InstanceGroupTimeline Source #

Creates a value of InstanceGroupTimeline with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

igtReadyDateTime :: Lens' InstanceGroupTimeline (Maybe UTCTime) Source #

The date and time when the instance group became ready to perform tasks.

igtCreationDateTime :: Lens' InstanceGroupTimeline (Maybe UTCTime) Source #

The creation date and time of the instance group.

igtEndDateTime :: Lens' InstanceGroupTimeline (Maybe UTCTime) Source #

The date and time when the instance group terminated.

InstanceResizePolicy

data InstanceResizePolicy Source #

Custom policy for requesting termination protection or termination of specific instances when shrinking an instance group.

See: instanceResizePolicy smart constructor.

Instances

Eq InstanceResizePolicy Source # 
Data InstanceResizePolicy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceResizePolicy -> c InstanceResizePolicy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceResizePolicy #

toConstr :: InstanceResizePolicy -> Constr #

dataTypeOf :: InstanceResizePolicy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceResizePolicy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceResizePolicy) #

gmapT :: (forall b. Data b => b -> b) -> InstanceResizePolicy -> InstanceResizePolicy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceResizePolicy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceResizePolicy -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceResizePolicy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceResizePolicy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceResizePolicy -> m InstanceResizePolicy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceResizePolicy -> m InstanceResizePolicy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceResizePolicy -> m InstanceResizePolicy #

Read InstanceResizePolicy Source # 
Show InstanceResizePolicy Source # 
Generic InstanceResizePolicy Source # 
Hashable InstanceResizePolicy Source # 
ToJSON InstanceResizePolicy Source # 
FromJSON InstanceResizePolicy Source # 
NFData InstanceResizePolicy Source # 

Methods

rnf :: InstanceResizePolicy -> () #

type Rep InstanceResizePolicy Source # 
type Rep InstanceResizePolicy = D1 * (MetaData "InstanceResizePolicy" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceResizePolicy'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_irpInstancesToProtect") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_irpInstancesToTerminate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_irpInstanceTerminationTimeout") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))))

instanceResizePolicy :: InstanceResizePolicy Source #

Creates a value of InstanceResizePolicy with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

irpInstancesToProtect :: Lens' InstanceResizePolicy [Text] Source #

Specific list of instances to be protected when shrinking an instance group.

irpInstancesToTerminate :: Lens' InstanceResizePolicy [Text] Source #

Specific list of instances to be terminated when shrinking an instance group.

irpInstanceTerminationTimeout :: Lens' InstanceResizePolicy (Maybe Int) Source #

Decommissioning timeout override for the specific list of instances to be terminated.

InstanceStateChangeReason

data InstanceStateChangeReason Source #

The details of the status change reason for the instance.

See: instanceStateChangeReason smart constructor.

Instances

Eq InstanceStateChangeReason Source # 
Data InstanceStateChangeReason Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceStateChangeReason -> c InstanceStateChangeReason #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceStateChangeReason #

toConstr :: InstanceStateChangeReason -> Constr #

dataTypeOf :: InstanceStateChangeReason -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceStateChangeReason) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceStateChangeReason) #

gmapT :: (forall b. Data b => b -> b) -> InstanceStateChangeReason -> InstanceStateChangeReason #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceStateChangeReason -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceStateChangeReason -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceStateChangeReason -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceStateChangeReason -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceStateChangeReason -> m InstanceStateChangeReason #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceStateChangeReason -> m InstanceStateChangeReason #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceStateChangeReason -> m InstanceStateChangeReason #

Read InstanceStateChangeReason Source # 
Show InstanceStateChangeReason Source # 
Generic InstanceStateChangeReason Source # 
Hashable InstanceStateChangeReason Source # 
FromJSON InstanceStateChangeReason Source # 
NFData InstanceStateChangeReason Source # 
type Rep InstanceStateChangeReason Source # 
type Rep InstanceStateChangeReason = D1 * (MetaData "InstanceStateChangeReason" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceStateChangeReason'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_iscrCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceStateChangeReasonCode))) (S1 * (MetaSel (Just Symbol "_iscrMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

instanceStateChangeReason :: InstanceStateChangeReason Source #

Creates a value of InstanceStateChangeReason with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • iscrCode - The programmable code for the state change reason.
  • iscrMessage - The status change reason description.

iscrCode :: Lens' InstanceStateChangeReason (Maybe InstanceStateChangeReasonCode) Source #

The programmable code for the state change reason.

iscrMessage :: Lens' InstanceStateChangeReason (Maybe Text) Source #

The status change reason description.

InstanceStatus

data InstanceStatus Source #

The instance status details.

See: instanceStatus smart constructor.

Instances

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 #

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 -> () #

type Rep InstanceStatus Source # 
type Rep InstanceStatus = D1 * (MetaData "InstanceStatus" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_isState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_isStateChangeReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceStateChangeReason))) (S1 * (MetaSel (Just Symbol "_isTimeline") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceTimeline))))))

instanceStatus :: InstanceStatus Source #

Creates a value of InstanceStatus with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • isState - The current state of the instance.
  • isStateChangeReason - The details of the status change reason for the instance.
  • isTimeline - The timeline of the instance status over time.

isState :: Lens' InstanceStatus (Maybe InstanceState) Source #

The current state of the instance.

isStateChangeReason :: Lens' InstanceStatus (Maybe InstanceStateChangeReason) Source #

The details of the status change reason for the instance.

isTimeline :: Lens' InstanceStatus (Maybe InstanceTimeline) Source #

The timeline of the instance status over time.

InstanceTimeline

data InstanceTimeline Source #

The timeline of the instance lifecycle.

See: instanceTimeline smart constructor.

Instances

Eq InstanceTimeline Source # 
Data InstanceTimeline Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceTimeline -> c InstanceTimeline #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceTimeline #

toConstr :: InstanceTimeline -> Constr #

dataTypeOf :: InstanceTimeline -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceTimeline) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceTimeline) #

gmapT :: (forall b. Data b => b -> b) -> InstanceTimeline -> InstanceTimeline #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceTimeline -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceTimeline -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceTimeline -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceTimeline -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceTimeline -> m InstanceTimeline #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceTimeline -> m InstanceTimeline #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceTimeline -> m InstanceTimeline #

Read InstanceTimeline Source # 
Show InstanceTimeline Source # 
Generic InstanceTimeline Source # 
Hashable InstanceTimeline Source # 
FromJSON InstanceTimeline Source # 
NFData InstanceTimeline Source # 

Methods

rnf :: InstanceTimeline -> () #

type Rep InstanceTimeline Source # 
type Rep InstanceTimeline = D1 * (MetaData "InstanceTimeline" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceTimeline'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_itReadyDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_itCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_itEndDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))

instanceTimeline :: InstanceTimeline Source #

Creates a value of InstanceTimeline with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

itReadyDateTime :: Lens' InstanceTimeline (Maybe UTCTime) Source #

The date and time when the instance was ready to perform tasks.

itCreationDateTime :: Lens' InstanceTimeline (Maybe UTCTime) Source #

The creation date and time of the instance.

itEndDateTime :: Lens' InstanceTimeline (Maybe UTCTime) Source #

The date and time when the instance was terminated.

InstanceTypeConfig

data InstanceTypeConfig Source #

An instance type configuration for each instance type in an instance fleet, which determines the EC2 instances Amazon EMR attempts to provision to fulfill On-Demand and Spot target capacities. There can be a maximum of 5 instance type configurations in a fleet.

See: instanceTypeConfig smart constructor.

Instances

Eq InstanceTypeConfig Source # 
Data InstanceTypeConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceTypeConfig -> c InstanceTypeConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceTypeConfig #

toConstr :: InstanceTypeConfig -> Constr #

dataTypeOf :: InstanceTypeConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceTypeConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceTypeConfig) #

gmapT :: (forall b. Data b => b -> b) -> InstanceTypeConfig -> InstanceTypeConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceTypeConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceTypeConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceTypeConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceTypeConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceTypeConfig -> m InstanceTypeConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceTypeConfig -> m InstanceTypeConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceTypeConfig -> m InstanceTypeConfig #

Read InstanceTypeConfig Source # 
Show InstanceTypeConfig Source # 
Generic InstanceTypeConfig Source # 
Hashable InstanceTypeConfig Source # 
ToJSON InstanceTypeConfig Source # 
NFData InstanceTypeConfig Source # 

Methods

rnf :: InstanceTypeConfig -> () #

type Rep InstanceTypeConfig Source # 
type Rep InstanceTypeConfig = D1 * (MetaData "InstanceTypeConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceTypeConfig'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_itcEBSConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe EBSConfiguration))) ((:*:) * (S1 * (MetaSel (Just Symbol "_itcBidPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_itcWeightedCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_itcConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Configuration]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_itcBidPriceAsPercentageOfOnDemandPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_itcInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))))

instanceTypeConfig Source #

Creates a value of InstanceTypeConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • itcEBSConfiguration - The configuration of Amazon Elastic Block Storage (EBS) attached to each instance as defined by InstanceType .
  • itcBidPrice - The bid price for each EC2 Spot instance type as defined by InstanceType . Expressed in USD. If neither BidPrice nor BidPriceAsPercentageOfOnDemandPrice is provided, BidPriceAsPercentageOfOnDemandPrice defaults to 100%.
  • itcWeightedCapacity - The number of units that a provisioned instance of this type provides toward fulfilling the target capacities defined in InstanceFleetConfig . This value is 1 for a master instance fleet, and must be 1 or greater for core and task instance fleets. Defaults to 1 if not specified.
  • itcConfigurations - A configuration classification that applies when provisioning cluster instances, which can include configurations for applications and software that run on the cluster.
  • itcBidPriceAsPercentageOfOnDemandPrice - The bid price, as a percentage of On-Demand price, for each EC2 Spot instance as defined by InstanceType . Expressed as a number (for example, 20 specifies 20%). If neither BidPrice nor BidPriceAsPercentageOfOnDemandPrice is provided, BidPriceAsPercentageOfOnDemandPrice defaults to 100%.
  • itcInstanceType - An EC2 instance type, such as m3.xlarge .

itcEBSConfiguration :: Lens' InstanceTypeConfig (Maybe EBSConfiguration) Source #

The configuration of Amazon Elastic Block Storage (EBS) attached to each instance as defined by InstanceType .

itcBidPrice :: Lens' InstanceTypeConfig (Maybe Text) Source #

The bid price for each EC2 Spot instance type as defined by InstanceType . Expressed in USD. If neither BidPrice nor BidPriceAsPercentageOfOnDemandPrice is provided, BidPriceAsPercentageOfOnDemandPrice defaults to 100%.

itcWeightedCapacity :: Lens' InstanceTypeConfig (Maybe Natural) Source #

The number of units that a provisioned instance of this type provides toward fulfilling the target capacities defined in InstanceFleetConfig . This value is 1 for a master instance fleet, and must be 1 or greater for core and task instance fleets. Defaults to 1 if not specified.

itcConfigurations :: Lens' InstanceTypeConfig [Configuration] Source #

A configuration classification that applies when provisioning cluster instances, which can include configurations for applications and software that run on the cluster.

itcBidPriceAsPercentageOfOnDemandPrice :: Lens' InstanceTypeConfig (Maybe Double) Source #

The bid price, as a percentage of On-Demand price, for each EC2 Spot instance as defined by InstanceType . Expressed as a number (for example, 20 specifies 20%). If neither BidPrice nor BidPriceAsPercentageOfOnDemandPrice is provided, BidPriceAsPercentageOfOnDemandPrice defaults to 100%.

itcInstanceType :: Lens' InstanceTypeConfig Text Source #

An EC2 instance type, such as m3.xlarge .

InstanceTypeSpecification

data InstanceTypeSpecification Source #

The configuration specification for each instance type in an instance fleet.

See: instanceTypeSpecification smart constructor.

Instances

Eq InstanceTypeSpecification Source # 
Data InstanceTypeSpecification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceTypeSpecification -> c InstanceTypeSpecification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceTypeSpecification #

toConstr :: InstanceTypeSpecification -> Constr #

dataTypeOf :: InstanceTypeSpecification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceTypeSpecification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceTypeSpecification) #

gmapT :: (forall b. Data b => b -> b) -> InstanceTypeSpecification -> InstanceTypeSpecification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceTypeSpecification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceTypeSpecification -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceTypeSpecification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceTypeSpecification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceTypeSpecification -> m InstanceTypeSpecification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceTypeSpecification -> m InstanceTypeSpecification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceTypeSpecification -> m InstanceTypeSpecification #

Read InstanceTypeSpecification Source # 
Show InstanceTypeSpecification Source # 
Generic InstanceTypeSpecification Source # 
Hashable InstanceTypeSpecification Source # 
FromJSON InstanceTypeSpecification Source # 
NFData InstanceTypeSpecification Source # 
type Rep InstanceTypeSpecification Source # 
type Rep InstanceTypeSpecification = D1 * (MetaData "InstanceTypeSpecification" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "InstanceTypeSpecification'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_itsBidPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_itsWeightedCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_itsConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Configuration]))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_itsEBSBlockDevices") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [EBSBlockDevice]))) (S1 * (MetaSel (Just Symbol "_itsInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_itsEBSOptimized") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_itsBidPriceAsPercentageOfOnDemandPrice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double)))))))

instanceTypeSpecification :: InstanceTypeSpecification Source #

Creates a value of InstanceTypeSpecification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • itsBidPrice - The bid price for each EC2 Spot instance type as defined by InstanceType . Expressed in USD.
  • itsWeightedCapacity - The number of units that a provisioned instance of this type provides toward fulfilling the target capacities defined in InstanceFleetConfig . Capacity values represent performance characteristics such as vCPUs, memory, or I/O. If not specified, the default value is 1.
  • itsConfigurations - A configuration classification that applies when provisioning cluster instances, which can include configurations for applications and software bundled with Amazon EMR.
  • itsEBSBlockDevices - The configuration of Amazon Elastic Block Storage (EBS) attached to each instance as defined by InstanceType .
  • itsInstanceType - The EC2 instance type, for example m3.xlarge .
  • itsEBSOptimized - Evaluates to TRUE when the specified InstanceType is EBS-optimized.
  • itsBidPriceAsPercentageOfOnDemandPrice - The bid price, as a percentage of On-Demand price, for each EC2 Spot instance as defined by InstanceType . Expressed as a number (for example, 20 specifies 20%).

itsBidPrice :: Lens' InstanceTypeSpecification (Maybe Text) Source #

The bid price for each EC2 Spot instance type as defined by InstanceType . Expressed in USD.

itsWeightedCapacity :: Lens' InstanceTypeSpecification (Maybe Natural) Source #

The number of units that a provisioned instance of this type provides toward fulfilling the target capacities defined in InstanceFleetConfig . Capacity values represent performance characteristics such as vCPUs, memory, or I/O. If not specified, the default value is 1.

itsConfigurations :: Lens' InstanceTypeSpecification [Configuration] Source #

A configuration classification that applies when provisioning cluster instances, which can include configurations for applications and software bundled with Amazon EMR.

itsEBSBlockDevices :: Lens' InstanceTypeSpecification [EBSBlockDevice] Source #

The configuration of Amazon Elastic Block Storage (EBS) attached to each instance as defined by InstanceType .

itsInstanceType :: Lens' InstanceTypeSpecification (Maybe Text) Source #

The EC2 instance type, for example m3.xlarge .

itsEBSOptimized :: Lens' InstanceTypeSpecification (Maybe Bool) Source #

Evaluates to TRUE when the specified InstanceType is EBS-optimized.

itsBidPriceAsPercentageOfOnDemandPrice :: Lens' InstanceTypeSpecification (Maybe Double) Source #

The bid price, as a percentage of On-Demand price, for each EC2 Spot instance as defined by InstanceType . Expressed as a number (for example, 20 specifies 20%).

JobFlowInstancesConfig

data JobFlowInstancesConfig Source #

A description of the Amazon EC2 instance on which the cluster (job flow) runs. A valid JobFlowInstancesConfig must contain either InstanceGroups or InstanceFleets, which is the recommended configuration. They cannot be used together. You may also have MasterInstanceType, SlaveInstanceType, and InstanceCount (all three must be present), but we don't recommend this configuration.

See: jobFlowInstancesConfig smart constructor.

Instances

Eq JobFlowInstancesConfig Source # 
Data JobFlowInstancesConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JobFlowInstancesConfig -> c JobFlowInstancesConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JobFlowInstancesConfig #

toConstr :: JobFlowInstancesConfig -> Constr #

dataTypeOf :: JobFlowInstancesConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c JobFlowInstancesConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JobFlowInstancesConfig) #

gmapT :: (forall b. Data b => b -> b) -> JobFlowInstancesConfig -> JobFlowInstancesConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JobFlowInstancesConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JobFlowInstancesConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> JobFlowInstancesConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JobFlowInstancesConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JobFlowInstancesConfig -> m JobFlowInstancesConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JobFlowInstancesConfig -> m JobFlowInstancesConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JobFlowInstancesConfig -> m JobFlowInstancesConfig #

Read JobFlowInstancesConfig Source # 
Show JobFlowInstancesConfig Source # 
Generic JobFlowInstancesConfig Source # 
Hashable JobFlowInstancesConfig Source # 
ToJSON JobFlowInstancesConfig Source # 
NFData JobFlowInstancesConfig Source # 

Methods

rnf :: JobFlowInstancesConfig -> () #

type Rep JobFlowInstancesConfig Source # 
type Rep JobFlowInstancesConfig = D1 * (MetaData "JobFlowInstancesConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "JobFlowInstancesConfig'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jficInstanceFleets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [InstanceFleetConfig]))) (S1 * (MetaSel (Just Symbol "_jficEC2KeyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jficSlaveInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jficInstanceCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jficEmrManagedSlaveSecurityGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jficAdditionalSlaveSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jficEC2SubnetIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_jficHadoopVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jficAdditionalMasterSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_jficEmrManagedMasterSecurityGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jficEC2SubnetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jficMasterInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jficInstanceGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [InstanceGroupConfig]))) (S1 * (MetaSel (Just Symbol "_jficKeepJobFlowAliveWhenNoSteps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jficServiceAccessSecurityGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jficTerminationProtected") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_jficPlacement") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PlacementType)))))))))

jobFlowInstancesConfig :: JobFlowInstancesConfig Source #

Creates a value of JobFlowInstancesConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • jficInstanceFleets - Describes the EC2 instances and instance configurations for clusters that use the instance fleet configuration.
  • jficEC2KeyName - The name of the EC2 key pair that can be used to ssh to the master node as the user called "hadoop."
  • jficSlaveInstanceType - The EC2 instance type of the slave nodes.
  • jficInstanceCount - The number of EC2 instances in the cluster.
  • jficEmrManagedSlaveSecurityGroup - The identifier of the Amazon EC2 security group for the slave nodes.
  • jficAdditionalSlaveSecurityGroups - A list of additional Amazon EC2 security group IDs for the slave nodes.
  • jficEC2SubnetIds - Applies to clusters that use the instance fleet configuration. When multiple EC2 subnet IDs are specified, Amazon EMR evaluates them and launches instances in the optimal subnet.
  • jficHadoopVersion - The Hadoop version for the cluster. Valid inputs are "0.18" (deprecated), "0.20" (deprecated), "0.20.205" (deprecated), "1.0.3", "2.2.0", or "2.4.0". If you do not set this value, the default of 0.18 is used, unless the AmiVersion parameter is set in the RunJobFlow call, in which case the default version of Hadoop for that AMI version is used.
  • jficAdditionalMasterSecurityGroups - A list of additional Amazon EC2 security group IDs for the master node.
  • jficEmrManagedMasterSecurityGroup - The identifier of the Amazon EC2 security group for the master node.
  • jficEC2SubnetId - Applies to clusters that use the uniform instance group configuration. To launch the cluster in Amazon Virtual Private Cloud (Amazon VPC), set this parameter to the identifier of the Amazon VPC subnet where you want the cluster to launch. If you do not specify this value, the cluster launches in the normal Amazon Web Services cloud, outside of an Amazon VPC, if the account launching the cluster supports EC2 Classic networks in the region where the cluster launches. Amazon VPC currently does not support cluster compute quadruple extra large (cc1.4xlarge) instances. Thus you cannot specify the cc1.4xlarge instance type for clusters launched in an Amazon VPC.
  • jficMasterInstanceType - The EC2 instance type of the master node.
  • jficInstanceGroups - Configuration for the instance groups in a cluster.
  • jficKeepJobFlowAliveWhenNoSteps - Specifies whether the cluster should remain available after completing all steps.
  • jficServiceAccessSecurityGroup - The identifier of the Amazon EC2 security group for the Amazon EMR service to access clusters in VPC private subnets.
  • jficTerminationProtected - Specifies whether to lock the cluster to prevent the Amazon EC2 instances from being terminated by API call, user intervention, or in the event of a job-flow error.
  • jficPlacement - The Availability Zone in which the cluster runs.

jficInstanceFleets :: Lens' JobFlowInstancesConfig [InstanceFleetConfig] Source #

Describes the EC2 instances and instance configurations for clusters that use the instance fleet configuration.

jficEC2KeyName :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

The name of the EC2 key pair that can be used to ssh to the master node as the user called "hadoop."

jficSlaveInstanceType :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

The EC2 instance type of the slave nodes.

jficInstanceCount :: Lens' JobFlowInstancesConfig (Maybe Int) Source #

The number of EC2 instances in the cluster.

jficEmrManagedSlaveSecurityGroup :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

The identifier of the Amazon EC2 security group for the slave nodes.

jficAdditionalSlaveSecurityGroups :: Lens' JobFlowInstancesConfig [Text] Source #

A list of additional Amazon EC2 security group IDs for the slave nodes.

jficEC2SubnetIds :: Lens' JobFlowInstancesConfig [Text] Source #

Applies to clusters that use the instance fleet configuration. When multiple EC2 subnet IDs are specified, Amazon EMR evaluates them and launches instances in the optimal subnet.

jficHadoopVersion :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

The Hadoop version for the cluster. Valid inputs are "0.18" (deprecated), "0.20" (deprecated), "0.20.205" (deprecated), "1.0.3", "2.2.0", or "2.4.0". If you do not set this value, the default of 0.18 is used, unless the AmiVersion parameter is set in the RunJobFlow call, in which case the default version of Hadoop for that AMI version is used.

jficAdditionalMasterSecurityGroups :: Lens' JobFlowInstancesConfig [Text] Source #

A list of additional Amazon EC2 security group IDs for the master node.

jficEmrManagedMasterSecurityGroup :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

The identifier of the Amazon EC2 security group for the master node.

jficEC2SubnetId :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

Applies to clusters that use the uniform instance group configuration. To launch the cluster in Amazon Virtual Private Cloud (Amazon VPC), set this parameter to the identifier of the Amazon VPC subnet where you want the cluster to launch. If you do not specify this value, the cluster launches in the normal Amazon Web Services cloud, outside of an Amazon VPC, if the account launching the cluster supports EC2 Classic networks in the region where the cluster launches. Amazon VPC currently does not support cluster compute quadruple extra large (cc1.4xlarge) instances. Thus you cannot specify the cc1.4xlarge instance type for clusters launched in an Amazon VPC.

jficMasterInstanceType :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

The EC2 instance type of the master node.

jficInstanceGroups :: Lens' JobFlowInstancesConfig [InstanceGroupConfig] Source #

Configuration for the instance groups in a cluster.

jficKeepJobFlowAliveWhenNoSteps :: Lens' JobFlowInstancesConfig (Maybe Bool) Source #

Specifies whether the cluster should remain available after completing all steps.

jficServiceAccessSecurityGroup :: Lens' JobFlowInstancesConfig (Maybe Text) Source #

The identifier of the Amazon EC2 security group for the Amazon EMR service to access clusters in VPC private subnets.

jficTerminationProtected :: Lens' JobFlowInstancesConfig (Maybe Bool) Source #

Specifies whether to lock the cluster to prevent the Amazon EC2 instances from being terminated by API call, user intervention, or in the event of a job-flow error.

jficPlacement :: Lens' JobFlowInstancesConfig (Maybe PlacementType) Source #

The Availability Zone in which the cluster runs.

KerberosAttributes

data KerberosAttributes Source #

Attributes for Kerberos configuration when Kerberos authentication is enabled using a security configuration. For more information see Use Kerberos Authentication in the EMR Management Guide .

See: kerberosAttributes smart constructor.

Instances

Eq KerberosAttributes Source # 
Data KerberosAttributes Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KerberosAttributes -> c KerberosAttributes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KerberosAttributes #

toConstr :: KerberosAttributes -> Constr #

dataTypeOf :: KerberosAttributes -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c KerberosAttributes) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KerberosAttributes) #

gmapT :: (forall b. Data b => b -> b) -> KerberosAttributes -> KerberosAttributes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KerberosAttributes -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KerberosAttributes -> r #

gmapQ :: (forall d. Data d => d -> u) -> KerberosAttributes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KerberosAttributes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KerberosAttributes -> m KerberosAttributes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KerberosAttributes -> m KerberosAttributes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KerberosAttributes -> m KerberosAttributes #

Read KerberosAttributes Source # 
Show KerberosAttributes Source # 
Generic KerberosAttributes Source # 
Hashable KerberosAttributes Source # 
ToJSON KerberosAttributes Source # 
FromJSON KerberosAttributes Source # 
NFData KerberosAttributes Source # 

Methods

rnf :: KerberosAttributes -> () #

type Rep KerberosAttributes Source # 
type Rep KerberosAttributes = D1 * (MetaData "KerberosAttributes" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "KerberosAttributes'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_kaADDomainJoinPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_kaCrossRealmTrustPrincipalPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_kaADDomainJoinUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_kaRealm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_kaKdcAdminPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))))

kerberosAttributes Source #

Creates a value of KerberosAttributes with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • kaADDomainJoinPassword - The Active Directory password for ADDomainJoinUser .
  • kaCrossRealmTrustPrincipalPassword - Required only when establishing a cross-realm trust with a KDC in a different realm. The cross-realm principal password, which must be identical across realms.
  • kaADDomainJoinUser - Required only when establishing a cross-realm trust with an Active Directory domain. A user with sufficient privileges to join resources to the domain.
  • kaRealm - The name of the Kerberos realm to which all nodes in a cluster belong. For example, EC2.INTERNAL .
  • kaKdcAdminPassword - The password used within the cluster for the kadmin service on the cluster-dedicated KDC, which maintains Kerberos principals, password policies, and keytabs for the cluster.

kaADDomainJoinPassword :: Lens' KerberosAttributes (Maybe Text) Source #

The Active Directory password for ADDomainJoinUser .

kaCrossRealmTrustPrincipalPassword :: Lens' KerberosAttributes (Maybe Text) Source #

Required only when establishing a cross-realm trust with a KDC in a different realm. The cross-realm principal password, which must be identical across realms.

kaADDomainJoinUser :: Lens' KerberosAttributes (Maybe Text) Source #

Required only when establishing a cross-realm trust with an Active Directory domain. A user with sufficient privileges to join resources to the domain.

kaRealm :: Lens' KerberosAttributes Text Source #

The name of the Kerberos realm to which all nodes in a cluster belong. For example, EC2.INTERNAL .

kaKdcAdminPassword :: Lens' KerberosAttributes Text Source #

The password used within the cluster for the kadmin service on the cluster-dedicated KDC, which maintains Kerberos principals, password policies, and keytabs for the cluster.

KeyValue

data KeyValue Source #

A key value pair.

See: keyValue smart constructor.

Instances

Eq KeyValue Source # 
Data KeyValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyValue -> c KeyValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeyValue #

toConstr :: KeyValue -> Constr #

dataTypeOf :: KeyValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c KeyValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyValue) #

gmapT :: (forall b. Data b => b -> b) -> KeyValue -> KeyValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeyValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyValue -> m KeyValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyValue -> m KeyValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyValue -> m KeyValue #

Read KeyValue Source # 
Show KeyValue Source # 
Generic KeyValue Source # 

Associated Types

type Rep KeyValue :: * -> * #

Methods

from :: KeyValue -> Rep KeyValue x #

to :: Rep KeyValue x -> KeyValue #

Hashable KeyValue Source # 

Methods

hashWithSalt :: Int -> KeyValue -> Int #

hash :: KeyValue -> Int #

ToJSON KeyValue Source # 
NFData KeyValue Source # 

Methods

rnf :: KeyValue -> () #

type Rep KeyValue Source # 
type Rep KeyValue = D1 * (MetaData "KeyValue" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "KeyValue'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_kvValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_kvKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

keyValue :: KeyValue Source #

Creates a value of KeyValue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • kvValue - The value part of the identified key.
  • kvKey - The unique identifier of a key value pair.

kvValue :: Lens' KeyValue (Maybe Text) Source #

The value part of the identified key.

kvKey :: Lens' KeyValue (Maybe Text) Source #

The unique identifier of a key value pair.

MetricDimension

data MetricDimension Source #

A CloudWatch dimension, which is specified using a Key (known as a Name in CloudWatch), Value pair. By default, Amazon EMR uses one dimension whose Key is JobFlowID and Value is a variable representing the cluster ID, which is > {emr.clusterId} . This enables the rule to bootstrap when the cluster ID becomes available.

See: metricDimension smart constructor.

Instances

Eq MetricDimension Source # 
Data MetricDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricDimension -> c MetricDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricDimension #

toConstr :: MetricDimension -> Constr #

dataTypeOf :: MetricDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MetricDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricDimension) #

gmapT :: (forall b. Data b => b -> b) -> MetricDimension -> MetricDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricDimension -> m MetricDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDimension -> m MetricDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDimension -> m MetricDimension #

Read MetricDimension Source # 
Show MetricDimension Source # 
Generic MetricDimension Source # 
Hashable MetricDimension Source # 
ToJSON MetricDimension Source # 
FromJSON MetricDimension Source # 
NFData MetricDimension Source # 

Methods

rnf :: MetricDimension -> () #

type Rep MetricDimension Source # 
type Rep MetricDimension = D1 * (MetaData "MetricDimension" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "MetricDimension'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_mdValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_mdKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

metricDimension :: MetricDimension Source #

Creates a value of MetricDimension with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mdValue :: Lens' MetricDimension (Maybe Text) Source #

The dimension value.

mdKey :: Lens' MetricDimension (Maybe Text) Source #

The dimension name.

PlacementType

data PlacementType Source #

The Amazon EC2 Availability Zone configuration of the cluster (job flow).

See: placementType smart constructor.

Instances

Eq PlacementType Source # 
Data PlacementType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementType -> c PlacementType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementType #

toConstr :: PlacementType -> Constr #

dataTypeOf :: PlacementType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementType) #

gmapT :: (forall b. Data b => b -> b) -> PlacementType -> PlacementType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementType -> m PlacementType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementType -> m PlacementType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementType -> m PlacementType #

Read PlacementType Source # 
Show PlacementType Source # 
Generic PlacementType Source # 

Associated Types

type Rep PlacementType :: * -> * #

Hashable PlacementType Source # 
ToJSON PlacementType Source # 
NFData PlacementType Source # 

Methods

rnf :: PlacementType -> () #

type Rep PlacementType Source # 
type Rep PlacementType = D1 * (MetaData "PlacementType" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "PlacementType'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ptAvailabilityZones") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_ptAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

placementType :: PlacementType Source #

Creates a value of PlacementType with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ptAvailabilityZones - When multiple Availability Zones are specified, Amazon EMR evaluates them and launches instances in the optimal Availability Zone. AvailabilityZones is used for instance fleets, while AvailabilityZone (singular) is used for uniform instance groups.
  • ptAvailabilityZone - The Amazon EC2 Availability Zone for the cluster. AvailabilityZone is used for uniform instance groups, while AvailabilityZones (plural) is used for instance fleets.

ptAvailabilityZones :: Lens' PlacementType [Text] Source #

When multiple Availability Zones are specified, Amazon EMR evaluates them and launches instances in the optimal Availability Zone. AvailabilityZones is used for instance fleets, while AvailabilityZone (singular) is used for uniform instance groups.

ptAvailabilityZone :: Lens' PlacementType (Maybe Text) Source #

The Amazon EC2 Availability Zone for the cluster. AvailabilityZone is used for uniform instance groups, while AvailabilityZones (plural) is used for instance fleets.

ScalingAction

data ScalingAction Source #

The type of adjustment the automatic scaling activity makes when triggered, and the periodicity of the adjustment.

See: scalingAction smart constructor.

Instances

Eq ScalingAction Source # 
Data ScalingAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScalingAction -> c ScalingAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScalingAction #

toConstr :: ScalingAction -> Constr #

dataTypeOf :: ScalingAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ScalingAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScalingAction) #

gmapT :: (forall b. Data b => b -> b) -> ScalingAction -> ScalingAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScalingAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScalingAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScalingAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScalingAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScalingAction -> m ScalingAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingAction -> m ScalingAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingAction -> m ScalingAction #

Read ScalingAction Source # 
Show ScalingAction Source # 
Generic ScalingAction Source # 

Associated Types

type Rep ScalingAction :: * -> * #

Hashable ScalingAction Source # 
ToJSON ScalingAction Source # 
FromJSON ScalingAction Source # 
NFData ScalingAction Source # 

Methods

rnf :: ScalingAction -> () #

type Rep ScalingAction Source # 
type Rep ScalingAction = D1 * (MetaData "ScalingAction" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ScalingAction'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_saMarket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe MarketType))) (S1 * (MetaSel (Just Symbol "_saSimpleScalingPolicyConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SimpleScalingPolicyConfiguration))))

scalingAction Source #

Creates a value of ScalingAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • saMarket - Not available for instance groups. Instance groups use the market type specified for the group.
  • saSimpleScalingPolicyConfiguration - The type of adjustment the automatic scaling activity makes when triggered, and the periodicity of the adjustment.

saMarket :: Lens' ScalingAction (Maybe MarketType) Source #

Not available for instance groups. Instance groups use the market type specified for the group.

saSimpleScalingPolicyConfiguration :: Lens' ScalingAction SimpleScalingPolicyConfiguration Source #

The type of adjustment the automatic scaling activity makes when triggered, and the periodicity of the adjustment.

ScalingConstraints

data ScalingConstraints Source #

The upper and lower EC2 instance limits for an automatic scaling policy. Automatic scaling activities triggered by automatic scaling rules will not cause an instance group to grow above or below these limits.

See: scalingConstraints smart constructor.

Instances

Eq ScalingConstraints Source # 
Data ScalingConstraints Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScalingConstraints -> c ScalingConstraints #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScalingConstraints #

toConstr :: ScalingConstraints -> Constr #

dataTypeOf :: ScalingConstraints -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ScalingConstraints) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScalingConstraints) #

gmapT :: (forall b. Data b => b -> b) -> ScalingConstraints -> ScalingConstraints #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScalingConstraints -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScalingConstraints -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScalingConstraints -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScalingConstraints -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScalingConstraints -> m ScalingConstraints #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingConstraints -> m ScalingConstraints #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingConstraints -> m ScalingConstraints #

Read ScalingConstraints Source # 
Show ScalingConstraints Source # 
Generic ScalingConstraints Source # 
Hashable ScalingConstraints Source # 
ToJSON ScalingConstraints Source # 
FromJSON ScalingConstraints Source # 
NFData ScalingConstraints Source # 

Methods

rnf :: ScalingConstraints -> () #

type Rep ScalingConstraints Source # 
type Rep ScalingConstraints = D1 * (MetaData "ScalingConstraints" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ScalingConstraints'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_scMinCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_scMaxCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))

scalingConstraints Source #

Creates a value of ScalingConstraints with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • scMinCapacity - The lower boundary of EC2 instances in an instance group below which scaling activities are not allowed to shrink. Scale-in activities will not terminate instances below this boundary.
  • scMaxCapacity - The upper boundary of EC2 instances in an instance group beyond which scaling activities are not allowed to grow. Scale-out activities will not add instances beyond this boundary.

scMinCapacity :: Lens' ScalingConstraints Int Source #

The lower boundary of EC2 instances in an instance group below which scaling activities are not allowed to shrink. Scale-in activities will not terminate instances below this boundary.

scMaxCapacity :: Lens' ScalingConstraints Int Source #

The upper boundary of EC2 instances in an instance group beyond which scaling activities are not allowed to grow. Scale-out activities will not add instances beyond this boundary.

ScalingRule

data ScalingRule Source #

A scale-in or scale-out rule that defines scaling activity, including the CloudWatch metric alarm that triggers activity, how EC2 instances are added or removed, and the periodicity of adjustments. The automatic scaling policy for an instance group can comprise one or more automatic scaling rules.

See: scalingRule smart constructor.

Instances

Eq ScalingRule Source # 
Data ScalingRule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScalingRule -> c ScalingRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScalingRule #

toConstr :: ScalingRule -> Constr #

dataTypeOf :: ScalingRule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ScalingRule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScalingRule) #

gmapT :: (forall b. Data b => b -> b) -> ScalingRule -> ScalingRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScalingRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScalingRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScalingRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScalingRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScalingRule -> m ScalingRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingRule -> m ScalingRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingRule -> m ScalingRule #

Read ScalingRule Source # 
Show ScalingRule Source # 
Generic ScalingRule Source # 

Associated Types

type Rep ScalingRule :: * -> * #

Hashable ScalingRule Source # 
ToJSON ScalingRule Source # 
FromJSON ScalingRule Source # 
NFData ScalingRule Source # 

Methods

rnf :: ScalingRule -> () #

type Rep ScalingRule Source # 
type Rep ScalingRule = D1 * (MetaData "ScalingRule" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ScalingRule'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_srDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_srName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_srAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ScalingAction)) (S1 * (MetaSel (Just Symbol "_srTrigger") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ScalingTrigger)))))

scalingRule Source #

Creates a value of ScalingRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • srDescription - A friendly, more verbose description of the automatic scaling rule.
  • srName - The name used to identify an automatic scaling rule. Rule names must be unique within a scaling policy.
  • srAction - The conditions that trigger an automatic scaling activity.
  • srTrigger - The CloudWatch alarm definition that determines when automatic scaling activity is triggered.

srDescription :: Lens' ScalingRule (Maybe Text) Source #

A friendly, more verbose description of the automatic scaling rule.

srName :: Lens' ScalingRule Text Source #

The name used to identify an automatic scaling rule. Rule names must be unique within a scaling policy.

srAction :: Lens' ScalingRule ScalingAction Source #

The conditions that trigger an automatic scaling activity.

srTrigger :: Lens' ScalingRule ScalingTrigger Source #

The CloudWatch alarm definition that determines when automatic scaling activity is triggered.

ScalingTrigger

data ScalingTrigger Source #

The conditions that trigger an automatic scaling activity.

See: scalingTrigger smart constructor.

Instances

Eq ScalingTrigger Source # 
Data ScalingTrigger Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScalingTrigger -> c ScalingTrigger #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScalingTrigger #

toConstr :: ScalingTrigger -> Constr #

dataTypeOf :: ScalingTrigger -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ScalingTrigger) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScalingTrigger) #

gmapT :: (forall b. Data b => b -> b) -> ScalingTrigger -> ScalingTrigger #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScalingTrigger -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScalingTrigger -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScalingTrigger -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScalingTrigger -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScalingTrigger -> m ScalingTrigger #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingTrigger -> m ScalingTrigger #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingTrigger -> m ScalingTrigger #

Read ScalingTrigger Source # 
Show ScalingTrigger Source # 
Generic ScalingTrigger Source # 

Associated Types

type Rep ScalingTrigger :: * -> * #

Hashable ScalingTrigger Source # 
ToJSON ScalingTrigger Source # 
FromJSON ScalingTrigger Source # 
NFData ScalingTrigger Source # 

Methods

rnf :: ScalingTrigger -> () #

type Rep ScalingTrigger Source # 
type Rep ScalingTrigger = D1 * (MetaData "ScalingTrigger" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" True) (C1 * (MetaCons "ScalingTrigger'" PrefixI True) (S1 * (MetaSel (Just Symbol "_stCloudWatchAlarmDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CloudWatchAlarmDefinition)))

scalingTrigger Source #

Creates a value of ScalingTrigger with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • stCloudWatchAlarmDefinition - The definition of a CloudWatch metric alarm. When the defined alarm conditions are met along with other trigger parameters, scaling activity begins.

stCloudWatchAlarmDefinition :: Lens' ScalingTrigger CloudWatchAlarmDefinition Source #

The definition of a CloudWatch metric alarm. When the defined alarm conditions are met along with other trigger parameters, scaling activity begins.

ScriptBootstrapActionConfig

data ScriptBootstrapActionConfig Source #

Configuration of the script to run during a bootstrap action.

See: scriptBootstrapActionConfig smart constructor.

Instances

Eq ScriptBootstrapActionConfig Source # 
Data ScriptBootstrapActionConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptBootstrapActionConfig -> c ScriptBootstrapActionConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptBootstrapActionConfig #

toConstr :: ScriptBootstrapActionConfig -> Constr #

dataTypeOf :: ScriptBootstrapActionConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ScriptBootstrapActionConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptBootstrapActionConfig) #

gmapT :: (forall b. Data b => b -> b) -> ScriptBootstrapActionConfig -> ScriptBootstrapActionConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptBootstrapActionConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptBootstrapActionConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScriptBootstrapActionConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptBootstrapActionConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptBootstrapActionConfig -> m ScriptBootstrapActionConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptBootstrapActionConfig -> m ScriptBootstrapActionConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptBootstrapActionConfig -> m ScriptBootstrapActionConfig #

Read ScriptBootstrapActionConfig Source # 
Show ScriptBootstrapActionConfig Source # 
Generic ScriptBootstrapActionConfig Source # 
Hashable ScriptBootstrapActionConfig Source # 
ToJSON ScriptBootstrapActionConfig Source # 
NFData ScriptBootstrapActionConfig Source # 
type Rep ScriptBootstrapActionConfig Source # 
type Rep ScriptBootstrapActionConfig = D1 * (MetaData "ScriptBootstrapActionConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ScriptBootstrapActionConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sbacArgs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_sbacPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

scriptBootstrapActionConfig Source #

Creates a value of ScriptBootstrapActionConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sbacArgs - A list of command line arguments to pass to the bootstrap action script.
  • sbacPath - Location of the script to run during a bootstrap action. Can be either a location in Amazon S3 or on a local file system.

sbacArgs :: Lens' ScriptBootstrapActionConfig [Text] Source #

A list of command line arguments to pass to the bootstrap action script.

sbacPath :: Lens' ScriptBootstrapActionConfig Text Source #

Location of the script to run during a bootstrap action. Can be either a location in Amazon S3 or on a local file system.

SecurityConfigurationSummary

data SecurityConfigurationSummary Source #

The creation date and time, and name, of a security configuration.

See: securityConfigurationSummary smart constructor.

Instances

Eq SecurityConfigurationSummary Source # 
Data SecurityConfigurationSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecurityConfigurationSummary -> c SecurityConfigurationSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecurityConfigurationSummary #

toConstr :: SecurityConfigurationSummary -> Constr #

dataTypeOf :: SecurityConfigurationSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecurityConfigurationSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecurityConfigurationSummary) #

gmapT :: (forall b. Data b => b -> b) -> SecurityConfigurationSummary -> SecurityConfigurationSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecurityConfigurationSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecurityConfigurationSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecurityConfigurationSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecurityConfigurationSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecurityConfigurationSummary -> m SecurityConfigurationSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityConfigurationSummary -> m SecurityConfigurationSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityConfigurationSummary -> m SecurityConfigurationSummary #

Read SecurityConfigurationSummary Source # 
Show SecurityConfigurationSummary Source # 
Generic SecurityConfigurationSummary Source # 
Hashable SecurityConfigurationSummary Source # 
FromJSON SecurityConfigurationSummary Source # 
NFData SecurityConfigurationSummary Source # 
type Rep SecurityConfigurationSummary Source # 
type Rep SecurityConfigurationSummary = D1 * (MetaData "SecurityConfigurationSummary" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "SecurityConfigurationSummary'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_scsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_scsCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))

securityConfigurationSummary :: SecurityConfigurationSummary Source #

Creates a value of SecurityConfigurationSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

scsName :: Lens' SecurityConfigurationSummary (Maybe Text) Source #

The name of the security configuration.

scsCreationDateTime :: Lens' SecurityConfigurationSummary (Maybe UTCTime) Source #

The date and time the security configuration was created.

ShrinkPolicy

data ShrinkPolicy Source #

Policy for customizing shrink operations. Allows configuration of decommissioning timeout and targeted instance shrinking.

See: shrinkPolicy smart constructor.

Instances

Eq ShrinkPolicy Source # 
Data ShrinkPolicy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShrinkPolicy -> c ShrinkPolicy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShrinkPolicy #

toConstr :: ShrinkPolicy -> Constr #

dataTypeOf :: ShrinkPolicy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ShrinkPolicy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShrinkPolicy) #

gmapT :: (forall b. Data b => b -> b) -> ShrinkPolicy -> ShrinkPolicy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShrinkPolicy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShrinkPolicy -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShrinkPolicy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShrinkPolicy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShrinkPolicy -> m ShrinkPolicy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShrinkPolicy -> m ShrinkPolicy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShrinkPolicy -> m ShrinkPolicy #

Read ShrinkPolicy Source # 
Show ShrinkPolicy Source # 
Generic ShrinkPolicy Source # 

Associated Types

type Rep ShrinkPolicy :: * -> * #

Hashable ShrinkPolicy Source # 
ToJSON ShrinkPolicy Source # 
FromJSON ShrinkPolicy Source # 
NFData ShrinkPolicy Source # 

Methods

rnf :: ShrinkPolicy -> () #

type Rep ShrinkPolicy Source # 
type Rep ShrinkPolicy = D1 * (MetaData "ShrinkPolicy" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "ShrinkPolicy'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_spDecommissionTimeout") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_spInstanceResizePolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceResizePolicy)))))

shrinkPolicy :: ShrinkPolicy Source #

Creates a value of ShrinkPolicy with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • spDecommissionTimeout - The desired timeout for decommissioning an instance. Overrides the default YARN decommissioning timeout.
  • spInstanceResizePolicy - Custom policy for requesting termination protection or termination of specific instances when shrinking an instance group.

spDecommissionTimeout :: Lens' ShrinkPolicy (Maybe Int) Source #

The desired timeout for decommissioning an instance. Overrides the default YARN decommissioning timeout.

spInstanceResizePolicy :: Lens' ShrinkPolicy (Maybe InstanceResizePolicy) Source #

Custom policy for requesting termination protection or termination of specific instances when shrinking an instance group.

SimpleScalingPolicyConfiguration

data SimpleScalingPolicyConfiguration Source #

An automatic scaling configuration, which describes how the policy adds or removes instances, the cooldown period, and the number of EC2 instances that will be added each time the CloudWatch metric alarm condition is satisfied.

See: simpleScalingPolicyConfiguration smart constructor.

Instances

Eq SimpleScalingPolicyConfiguration Source # 
Data SimpleScalingPolicyConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SimpleScalingPolicyConfiguration -> c SimpleScalingPolicyConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SimpleScalingPolicyConfiguration #

toConstr :: SimpleScalingPolicyConfiguration -> Constr #

dataTypeOf :: SimpleScalingPolicyConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SimpleScalingPolicyConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SimpleScalingPolicyConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> SimpleScalingPolicyConfiguration -> SimpleScalingPolicyConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SimpleScalingPolicyConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SimpleScalingPolicyConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> SimpleScalingPolicyConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SimpleScalingPolicyConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SimpleScalingPolicyConfiguration -> m SimpleScalingPolicyConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleScalingPolicyConfiguration -> m SimpleScalingPolicyConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleScalingPolicyConfiguration -> m SimpleScalingPolicyConfiguration #

Read SimpleScalingPolicyConfiguration Source # 
Show SimpleScalingPolicyConfiguration Source # 
Generic SimpleScalingPolicyConfiguration Source # 
Hashable SimpleScalingPolicyConfiguration Source # 
ToJSON SimpleScalingPolicyConfiguration Source # 
FromJSON SimpleScalingPolicyConfiguration Source # 
NFData SimpleScalingPolicyConfiguration Source # 
type Rep SimpleScalingPolicyConfiguration Source # 
type Rep SimpleScalingPolicyConfiguration = D1 * (MetaData "SimpleScalingPolicyConfiguration" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "SimpleScalingPolicyConfiguration'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sspcAdjustmentType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AdjustmentType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sspcCoolDown") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_sspcScalingAdjustment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))))

simpleScalingPolicyConfiguration Source #

Creates a value of SimpleScalingPolicyConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sspcAdjustmentType - The way in which EC2 instances are added (if ScalingAdjustment is a positive number) or terminated (if ScalingAdjustment is a negative number) each time the scaling activity is triggered. CHANGE_IN_CAPACITY is the default. CHANGE_IN_CAPACITY indicates that the EC2 instance count increments or decrements by ScalingAdjustment , which should be expressed as an integer. PERCENT_CHANGE_IN_CAPACITY indicates the instance count increments or decrements by the percentage specified by ScalingAdjustment , which should be expressed as an integer. For example, 20 indicates an increase in 20% increments of cluster capacity. EXACT_CAPACITY indicates the scaling activity results in an instance group with the number of EC2 instances specified by ScalingAdjustment , which should be expressed as a positive integer.
  • sspcCoolDown - The amount of time, in seconds, after a scaling activity completes before any further trigger-related scaling activities can start. The default value is 0.
  • sspcScalingAdjustment - The amount by which to scale in or scale out, based on the specified AdjustmentType . A positive value adds to the instance group's EC2 instance count while a negative number removes instances. If AdjustmentType is set to EXACT_CAPACITY , the number should only be a positive integer. If AdjustmentType is set to PERCENT_CHANGE_IN_CAPACITY , the value should express the percentage as an integer. For example, -20 indicates a decrease in 20% increments of cluster capacity.

sspcAdjustmentType :: Lens' SimpleScalingPolicyConfiguration (Maybe AdjustmentType) Source #

The way in which EC2 instances are added (if ScalingAdjustment is a positive number) or terminated (if ScalingAdjustment is a negative number) each time the scaling activity is triggered. CHANGE_IN_CAPACITY is the default. CHANGE_IN_CAPACITY indicates that the EC2 instance count increments or decrements by ScalingAdjustment , which should be expressed as an integer. PERCENT_CHANGE_IN_CAPACITY indicates the instance count increments or decrements by the percentage specified by ScalingAdjustment , which should be expressed as an integer. For example, 20 indicates an increase in 20% increments of cluster capacity. EXACT_CAPACITY indicates the scaling activity results in an instance group with the number of EC2 instances specified by ScalingAdjustment , which should be expressed as a positive integer.

sspcCoolDown :: Lens' SimpleScalingPolicyConfiguration (Maybe Int) Source #

The amount of time, in seconds, after a scaling activity completes before any further trigger-related scaling activities can start. The default value is 0.

sspcScalingAdjustment :: Lens' SimpleScalingPolicyConfiguration Int Source #

The amount by which to scale in or scale out, based on the specified AdjustmentType . A positive value adds to the instance group's EC2 instance count while a negative number removes instances. If AdjustmentType is set to EXACT_CAPACITY , the number should only be a positive integer. If AdjustmentType is set to PERCENT_CHANGE_IN_CAPACITY , the value should express the percentage as an integer. For example, -20 indicates a decrease in 20% increments of cluster capacity.

SpotProvisioningSpecification

data SpotProvisioningSpecification Source #

The launch specification for Spot instances in the instance fleet, which determines the defined duration and provisioning timeout behavior.

See: spotProvisioningSpecification smart constructor.

Instances

Eq SpotProvisioningSpecification Source # 
Data SpotProvisioningSpecification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpotProvisioningSpecification -> c SpotProvisioningSpecification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpotProvisioningSpecification #

toConstr :: SpotProvisioningSpecification -> Constr #

dataTypeOf :: SpotProvisioningSpecification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SpotProvisioningSpecification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpotProvisioningSpecification) #

gmapT :: (forall b. Data b => b -> b) -> SpotProvisioningSpecification -> SpotProvisioningSpecification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpotProvisioningSpecification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpotProvisioningSpecification -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpotProvisioningSpecification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpotProvisioningSpecification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpotProvisioningSpecification -> m SpotProvisioningSpecification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpotProvisioningSpecification -> m SpotProvisioningSpecification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpotProvisioningSpecification -> m SpotProvisioningSpecification #

Read SpotProvisioningSpecification Source # 
Show SpotProvisioningSpecification Source # 
Generic SpotProvisioningSpecification Source # 
Hashable SpotProvisioningSpecification Source # 
ToJSON SpotProvisioningSpecification Source # 
FromJSON SpotProvisioningSpecification Source # 
NFData SpotProvisioningSpecification Source # 
type Rep SpotProvisioningSpecification Source # 
type Rep SpotProvisioningSpecification = D1 * (MetaData "SpotProvisioningSpecification" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "SpotProvisioningSpecification'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_spsBlockDurationMinutes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_spsTimeoutDurationMinutes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat)) (S1 * (MetaSel (Just Symbol "_spsTimeoutAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SpotProvisioningTimeoutAction)))))

spotProvisioningSpecification Source #

Creates a value of SpotProvisioningSpecification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • spsBlockDurationMinutes - The defined duration for Spot instances (also known as Spot blocks) in minutes. When specified, the Spot instance does not terminate before the defined duration expires, and defined duration pricing for Spot instances applies. Valid values are 60, 120, 180, 240, 300, or 360. The duration period starts as soon as a Spot instance receives its instance ID. At the end of the duration, Amazon EC2 marks the Spot instance for termination and provides a Spot instance termination notice, which gives the instance a two-minute warning before it terminates.
  • spsTimeoutDurationMinutes - The spot provisioning timeout period in minutes. If Spot instances are not provisioned within this time period, the TimeOutAction is taken. Minimum value is 5 and maximum value is 1440. The timeout applies only during initial provisioning, when the cluster is first created.
  • spsTimeoutAction - The action to take when TargetSpotCapacity has not been fulfilled when the TimeoutDurationMinutes has expired. Spot instances are not uprovisioned within the Spot provisioining timeout. Valid values are TERMINATE_CLUSTER and SWITCH_TO_ON_DEMAND . SWITCH_TO_ON_DEMAND specifies that if no Spot instances are available, On-Demand Instances should be provisioned to fulfill any remaining Spot capacity.

spsBlockDurationMinutes :: Lens' SpotProvisioningSpecification (Maybe Natural) Source #

The defined duration for Spot instances (also known as Spot blocks) in minutes. When specified, the Spot instance does not terminate before the defined duration expires, and defined duration pricing for Spot instances applies. Valid values are 60, 120, 180, 240, 300, or 360. The duration period starts as soon as a Spot instance receives its instance ID. At the end of the duration, Amazon EC2 marks the Spot instance for termination and provides a Spot instance termination notice, which gives the instance a two-minute warning before it terminates.

spsTimeoutDurationMinutes :: Lens' SpotProvisioningSpecification Natural Source #

The spot provisioning timeout period in minutes. If Spot instances are not provisioned within this time period, the TimeOutAction is taken. Minimum value is 5 and maximum value is 1440. The timeout applies only during initial provisioning, when the cluster is first created.

spsTimeoutAction :: Lens' SpotProvisioningSpecification SpotProvisioningTimeoutAction Source #

The action to take when TargetSpotCapacity has not been fulfilled when the TimeoutDurationMinutes has expired. Spot instances are not uprovisioned within the Spot provisioining timeout. Valid values are TERMINATE_CLUSTER and SWITCH_TO_ON_DEMAND . SWITCH_TO_ON_DEMAND specifies that if no Spot instances are available, On-Demand Instances should be provisioned to fulfill any remaining Spot capacity.

Step

data Step Source #

This represents a step in a cluster.

See: step smart constructor.

Instances

Eq Step Source # 

Methods

(==) :: Step -> Step -> Bool #

(/=) :: Step -> Step -> Bool #

Data Step Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Step -> c Step #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Step #

toConstr :: Step -> Constr #

dataTypeOf :: Step -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Step) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Step) #

gmapT :: (forall b. Data b => b -> b) -> Step -> Step #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Step -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Step -> r #

gmapQ :: (forall d. Data d => d -> u) -> Step -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Step -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Step -> m Step #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Step -> m Step #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Step -> m Step #

Read Step Source # 
Show Step Source # 

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

Generic Step Source # 

Associated Types

type Rep Step :: * -> * #

Methods

from :: Step -> Rep Step x #

to :: Rep Step x -> Step #

Hashable Step Source # 

Methods

hashWithSalt :: Int -> Step -> Int #

hash :: Step -> Int #

FromJSON Step Source # 
NFData Step Source # 

Methods

rnf :: Step -> () #

type Rep Step Source # 

step :: Step Source #

Creates a value of Step with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sStatus - The current execution status details of the cluster step.
  • sActionOnFailure - This specifies what action to take when the cluster step fails. Possible values are TERMINATE_CLUSTER, CANCEL_AND_WAIT, and CONTINUE.
  • sConfig - The Hadoop job configuration of the cluster step.
  • sName - The name of the cluster step.
  • sId - The identifier of the cluster step.

sStatus :: Lens' Step (Maybe StepStatus) Source #

The current execution status details of the cluster step.

sActionOnFailure :: Lens' Step (Maybe ActionOnFailure) Source #

This specifies what action to take when the cluster step fails. Possible values are TERMINATE_CLUSTER, CANCEL_AND_WAIT, and CONTINUE.

sConfig :: Lens' Step (Maybe HadoopStepConfig) Source #

The Hadoop job configuration of the cluster step.

sName :: Lens' Step (Maybe Text) Source #

The name of the cluster step.

sId :: Lens' Step (Maybe Text) Source #

The identifier of the cluster step.

StepConfig

data StepConfig Source #

Specification of a cluster (job flow) step.

See: stepConfig smart constructor.

Instances

Eq StepConfig Source # 
Data StepConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StepConfig -> c StepConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StepConfig #

toConstr :: StepConfig -> Constr #

dataTypeOf :: StepConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StepConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StepConfig) #

gmapT :: (forall b. Data b => b -> b) -> StepConfig -> StepConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StepConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StepConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> StepConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StepConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StepConfig -> m StepConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StepConfig -> m StepConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StepConfig -> m StepConfig #

Read StepConfig Source # 
Show StepConfig Source # 
Generic StepConfig Source # 

Associated Types

type Rep StepConfig :: * -> * #

Hashable StepConfig Source # 
ToJSON StepConfig Source # 
NFData StepConfig Source # 

Methods

rnf :: StepConfig -> () #

type Rep StepConfig Source # 
type Rep StepConfig = D1 * (MetaData "StepConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "StepConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_scActionOnFailure") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ActionOnFailure))) ((:*:) * (S1 * (MetaSel (Just Symbol "_scName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_scHadoopJARStep") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HadoopJARStepConfig)))))

stepConfig Source #

Creates a value of StepConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

scActionOnFailure :: Lens' StepConfig (Maybe ActionOnFailure) Source #

The action to take if the step fails.

scName :: Lens' StepConfig Text Source #

The name of the step.

scHadoopJARStep :: Lens' StepConfig HadoopJARStepConfig Source #

The JAR file used for the step.

StepStateChangeReason

data StepStateChangeReason Source #

The details of the step state change reason.

See: stepStateChangeReason smart constructor.

Instances

Eq StepStateChangeReason Source # 
Data StepStateChangeReason Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StepStateChangeReason -> c StepStateChangeReason #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StepStateChangeReason #

toConstr :: StepStateChangeReason -> Constr #

dataTypeOf :: StepStateChangeReason -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StepStateChangeReason) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StepStateChangeReason) #

gmapT :: (forall b. Data b => b -> b) -> StepStateChangeReason -> StepStateChangeReason #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StepStateChangeReason -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StepStateChangeReason -> r #

gmapQ :: (forall d. Data d => d -> u) -> StepStateChangeReason -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StepStateChangeReason -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StepStateChangeReason -> m StepStateChangeReason #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StepStateChangeReason -> m StepStateChangeReason #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StepStateChangeReason -> m StepStateChangeReason #

Read StepStateChangeReason Source # 
Show StepStateChangeReason Source # 
Generic StepStateChangeReason Source # 
Hashable StepStateChangeReason Source # 
FromJSON StepStateChangeReason Source # 
NFData StepStateChangeReason Source # 

Methods

rnf :: StepStateChangeReason -> () #

type Rep StepStateChangeReason Source # 
type Rep StepStateChangeReason = D1 * (MetaData "StepStateChangeReason" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "StepStateChangeReason'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sscrCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StepStateChangeReasonCode))) (S1 * (MetaSel (Just Symbol "_sscrMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

stepStateChangeReason :: StepStateChangeReason Source #

Creates a value of StepStateChangeReason with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sscrCode - The programmable code for the state change reason. Note: Currently, the service provides no code for the state change.
  • sscrMessage - The descriptive message for the state change reason.

sscrCode :: Lens' StepStateChangeReason (Maybe StepStateChangeReasonCode) Source #

The programmable code for the state change reason. Note: Currently, the service provides no code for the state change.

sscrMessage :: Lens' StepStateChangeReason (Maybe Text) Source #

The descriptive message for the state change reason.

StepStatus

data StepStatus Source #

The execution status details of the cluster step.

See: stepStatus smart constructor.

Instances

Eq StepStatus Source # 
Data StepStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StepStatus -> c StepStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StepStatus #

toConstr :: StepStatus -> Constr #

dataTypeOf :: StepStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StepStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StepStatus) #

gmapT :: (forall b. Data b => b -> b) -> StepStatus -> StepStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StepStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StepStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> StepStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StepStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StepStatus -> m StepStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StepStatus -> m StepStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StepStatus -> m StepStatus #

Read StepStatus Source # 
Show StepStatus Source # 
Generic StepStatus Source # 

Associated Types

type Rep StepStatus :: * -> * #

Hashable StepStatus Source # 
FromJSON StepStatus Source # 
NFData StepStatus Source # 

Methods

rnf :: StepStatus -> () #

type Rep StepStatus Source # 
type Rep StepStatus = D1 * (MetaData "StepStatus" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "StepStatus'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ssState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StepState))) (S1 * (MetaSel (Just Symbol "_ssFailureDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe FailureDetails)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ssStateChangeReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StepStateChangeReason))) (S1 * (MetaSel (Just Symbol "_ssTimeline") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StepTimeline))))))

stepStatus :: StepStatus Source #

Creates a value of StepStatus with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssState - The execution state of the cluster step.
  • ssFailureDetails - The details for the step failure including reason, message, and log file path where the root cause was identified.
  • ssStateChangeReason - The reason for the step execution status change.
  • ssTimeline - The timeline of the cluster step status over time.

ssState :: Lens' StepStatus (Maybe StepState) Source #

The execution state of the cluster step.

ssFailureDetails :: Lens' StepStatus (Maybe FailureDetails) Source #

The details for the step failure including reason, message, and log file path where the root cause was identified.

ssStateChangeReason :: Lens' StepStatus (Maybe StepStateChangeReason) Source #

The reason for the step execution status change.

ssTimeline :: Lens' StepStatus (Maybe StepTimeline) Source #

The timeline of the cluster step status over time.

StepSummary

data StepSummary Source #

The summary of the cluster step.

See: stepSummary smart constructor.

Instances

Eq StepSummary Source # 
Data StepSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StepSummary -> c StepSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StepSummary #

toConstr :: StepSummary -> Constr #

dataTypeOf :: StepSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StepSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StepSummary) #

gmapT :: (forall b. Data b => b -> b) -> StepSummary -> StepSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StepSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StepSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> StepSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StepSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StepSummary -> m StepSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StepSummary -> m StepSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StepSummary -> m StepSummary #

Read StepSummary Source # 
Show StepSummary Source # 
Generic StepSummary Source # 

Associated Types

type Rep StepSummary :: * -> * #

Hashable StepSummary Source # 
FromJSON StepSummary Source # 
NFData StepSummary Source # 

Methods

rnf :: StepSummary -> () #

type Rep StepSummary Source # 

stepSummary :: StepSummary Source #

Creates a value of StepSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssStatus - The current execution status details of the cluster step.
  • ssActionOnFailure - This specifies what action to take when the cluster step fails. Possible values are TERMINATE_CLUSTER, CANCEL_AND_WAIT, and CONTINUE.
  • ssConfig - The Hadoop job configuration of the cluster step.
  • ssName - The name of the cluster step.
  • ssId - The identifier of the cluster step.

ssStatus :: Lens' StepSummary (Maybe StepStatus) Source #

The current execution status details of the cluster step.

ssActionOnFailure :: Lens' StepSummary (Maybe ActionOnFailure) Source #

This specifies what action to take when the cluster step fails. Possible values are TERMINATE_CLUSTER, CANCEL_AND_WAIT, and CONTINUE.

ssConfig :: Lens' StepSummary (Maybe HadoopStepConfig) Source #

The Hadoop job configuration of the cluster step.

ssName :: Lens' StepSummary (Maybe Text) Source #

The name of the cluster step.

ssId :: Lens' StepSummary (Maybe Text) Source #

The identifier of the cluster step.

StepTimeline

data StepTimeline Source #

The timeline of the cluster step lifecycle.

See: stepTimeline smart constructor.

Instances

Eq StepTimeline Source # 
Data StepTimeline Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StepTimeline -> c StepTimeline #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StepTimeline #

toConstr :: StepTimeline -> Constr #

dataTypeOf :: StepTimeline -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StepTimeline) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StepTimeline) #

gmapT :: (forall b. Data b => b -> b) -> StepTimeline -> StepTimeline #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StepTimeline -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StepTimeline -> r #

gmapQ :: (forall d. Data d => d -> u) -> StepTimeline -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StepTimeline -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StepTimeline -> m StepTimeline #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StepTimeline -> m StepTimeline #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StepTimeline -> m StepTimeline #

Read StepTimeline Source # 
Show StepTimeline Source # 
Generic StepTimeline Source # 

Associated Types

type Rep StepTimeline :: * -> * #

Hashable StepTimeline Source # 
FromJSON StepTimeline Source # 
NFData StepTimeline Source # 

Methods

rnf :: StepTimeline -> () #

type Rep StepTimeline Source # 
type Rep StepTimeline = D1 * (MetaData "StepTimeline" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "StepTimeline'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_stCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_stEndDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_stStartDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))

stepTimeline :: StepTimeline Source #

Creates a value of StepTimeline with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • stCreationDateTime - The date and time when the cluster step was created.
  • stEndDateTime - The date and time when the cluster step execution completed or failed.
  • stStartDateTime - The date and time when the cluster step execution started.

stCreationDateTime :: Lens' StepTimeline (Maybe UTCTime) Source #

The date and time when the cluster step was created.

stEndDateTime :: Lens' StepTimeline (Maybe UTCTime) Source #

The date and time when the cluster step execution completed or failed.

stStartDateTime :: Lens' StepTimeline (Maybe UTCTime) Source #

The date and time when the cluster step execution started.

SupportedProductConfig

data SupportedProductConfig Source #

The list of supported product configurations which allow user-supplied arguments. EMR accepts these arguments and forwards them to the corresponding installation script as bootstrap action arguments.

See: supportedProductConfig smart constructor.

Instances

Eq SupportedProductConfig Source # 
Data SupportedProductConfig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SupportedProductConfig -> c SupportedProductConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SupportedProductConfig #

toConstr :: SupportedProductConfig -> Constr #

dataTypeOf :: SupportedProductConfig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SupportedProductConfig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SupportedProductConfig) #

gmapT :: (forall b. Data b => b -> b) -> SupportedProductConfig -> SupportedProductConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SupportedProductConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SupportedProductConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> SupportedProductConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SupportedProductConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SupportedProductConfig -> m SupportedProductConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SupportedProductConfig -> m SupportedProductConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SupportedProductConfig -> m SupportedProductConfig #

Read SupportedProductConfig Source # 
Show SupportedProductConfig Source # 
Generic SupportedProductConfig Source # 
Hashable SupportedProductConfig Source # 
ToJSON SupportedProductConfig Source # 
NFData SupportedProductConfig Source # 

Methods

rnf :: SupportedProductConfig -> () #

type Rep SupportedProductConfig Source # 
type Rep SupportedProductConfig = D1 * (MetaData "SupportedProductConfig" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "SupportedProductConfig'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_spcArgs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_spcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

supportedProductConfig :: SupportedProductConfig Source #

Creates a value of SupportedProductConfig with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • spcArgs - The list of user-supplied arguments.
  • spcName - The name of the product configuration.

spcArgs :: Lens' SupportedProductConfig [Text] Source #

The list of user-supplied arguments.

spcName :: Lens' SupportedProductConfig (Maybe Text) Source #

The name of the product configuration.

Tag

data Tag Source #

A keyvalue pair containing user-defined metadata that you can associate with an Amazon EMR resource. Tags make it easier to associate clusters in various ways, such as grouping clusters to track your Amazon EMR resource allocation costs. For more information, see <http:docs.aws.amazon.comemrlatestManagementGuide/emr-plan-tags.html Tag Clusters> .

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Data Tag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
FromJSON Tag Source # 
NFData Tag Source # 

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
type Rep Tag = D1 * (MetaData "Tag" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "Tag'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

tag :: Tag Source #

Creates a value of Tag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tagValue - A user-defined value, which is optional in a tag. For more information, see Tag Clusters .
  • tagKey - A user-defined key, which is the minimum required information for a valid tag. For more information, see Tag .

tagValue :: Lens' Tag (Maybe Text) Source #

A user-defined value, which is optional in a tag. For more information, see Tag Clusters .

tagKey :: Lens' Tag (Maybe Text) Source #

A user-defined key, which is the minimum required information for a valid tag. For more information, see Tag .

VolumeSpecification

data VolumeSpecification Source #

EBS volume specifications such as volume type, IOPS, and size (GiB) that will be requested for the EBS volume attached to an EC2 instance in the cluster.

See: volumeSpecification smart constructor.

Instances

Eq VolumeSpecification Source # 
Data VolumeSpecification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VolumeSpecification -> c VolumeSpecification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VolumeSpecification #

toConstr :: VolumeSpecification -> Constr #

dataTypeOf :: VolumeSpecification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VolumeSpecification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VolumeSpecification) #

gmapT :: (forall b. Data b => b -> b) -> VolumeSpecification -> VolumeSpecification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VolumeSpecification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VolumeSpecification -> r #

gmapQ :: (forall d. Data d => d -> u) -> VolumeSpecification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VolumeSpecification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VolumeSpecification -> m VolumeSpecification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VolumeSpecification -> m VolumeSpecification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VolumeSpecification -> m VolumeSpecification #

Read VolumeSpecification Source # 
Show VolumeSpecification Source # 
Generic VolumeSpecification Source # 
Hashable VolumeSpecification Source # 
ToJSON VolumeSpecification Source # 
FromJSON VolumeSpecification Source # 
NFData VolumeSpecification Source # 

Methods

rnf :: VolumeSpecification -> () #

type Rep VolumeSpecification Source # 
type Rep VolumeSpecification = D1 * (MetaData "VolumeSpecification" "Network.AWS.EMR.Types.Product" "amazonka-emr-1.6.0-Gh02fq80On6JQmEHB2V13H" False) (C1 * (MetaCons "VolumeSpecification'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_vsIOPS") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_vsVolumeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_vsSizeInGB") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))))

volumeSpecification Source #

Creates a value of VolumeSpecification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • vsIOPS - The number of I/O operations per second (IOPS) that the volume supports.
  • vsVolumeType - The volume type. Volume types supported are gp2, io1, standard.
  • vsSizeInGB - The volume size, in gibibytes (GiB). This can be a number from 1 - 1024. If the volume type is EBS-optimized, the minimum value is 10.

vsIOPS :: Lens' VolumeSpecification (Maybe Int) Source #

The number of I/O operations per second (IOPS) that the volume supports.

vsVolumeType :: Lens' VolumeSpecification Text Source #

The volume type. Volume types supported are gp2, io1, standard.

vsSizeInGB :: Lens' VolumeSpecification Int Source #

The volume size, in gibibytes (GiB). This can be a number from 1 - 1024. If the volume type is EBS-optimized, the minimum value is 10.