amazonka-batch-1.6.1: Amazon Batch 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.Batch.Types

Contents

Description

 
Synopsis

Service Configuration

batch :: Service Source #

API version 2016-08-10 of the Amazon Batch SDK configuration.

Errors

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

These errors are usually caused by a server issue.

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

These errors are usually caused by a client action, such as using an action or resource on behalf of a user that doesn't have permissions to use the action or resource, or specifying an identifier that is not valid.

ArrayJobDependency

data ArrayJobDependency Source #

Constructors

NToN 
Sequential 
Instances
Bounded ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Data ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: ArrayJobDependency -> Constr #

dataTypeOf :: ArrayJobDependency -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep ArrayJobDependency :: Type -> Type #

Hashable ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToJSON ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromJSON ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToQuery ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromText ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToText ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

NFData ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: ArrayJobDependency -> () #

type Rep ArrayJobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep ArrayJobDependency = D1 (MetaData "ArrayJobDependency" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "NToN" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sequential" PrefixI False) (U1 :: Type -> Type))

CEState

data CEState Source #

Constructors

Disabled 
Enabled 
Instances
Bounded CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

Data CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: CEState -> Constr #

dataTypeOf :: CEState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep CEState :: Type -> Type #

Methods

from :: CEState -> Rep CEState x #

to :: Rep CEState x -> CEState #

Hashable CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

hashWithSalt :: Int -> CEState -> Int #

hash :: CEState -> Int #

ToJSON CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromJSON CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

ToQuery CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toBS :: CEState -> ByteString #

FromText CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToText CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toText :: CEState -> Text #

NFData CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: CEState -> () #

type Rep CEState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep CEState = D1 (MetaData "CEState" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "Disabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Enabled" PrefixI False) (U1 :: Type -> Type))

CEStatus

data CEStatus Source #

Instances
Bounded CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Data CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: CEStatus -> Constr #

dataTypeOf :: CEStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep CEStatus :: Type -> Type #

Methods

from :: CEStatus -> Rep CEStatus x #

to :: Rep CEStatus x -> CEStatus #

Hashable CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

hashWithSalt :: Int -> CEStatus -> Int #

hash :: CEStatus -> Int #

FromJSON CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

ToQuery CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toBS :: CEStatus -> ByteString #

FromText CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToText CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toText :: CEStatus -> Text #

NFData CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: CEStatus -> () #

type Rep CEStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep CEStatus = D1 (MetaData "CEStatus" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) ((C1 (MetaCons "CESCreating" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CESDeleted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CESDeleting" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "CESInvalid" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CESUpdating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CESValid" PrefixI False) (U1 :: Type -> Type))))

CEType

data CEType Source #

Constructors

Managed 
Unmanaged 
Instances
Bounded CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

Data CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: CEType -> Constr #

dataTypeOf :: CEType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep CEType :: Type -> Type #

Methods

from :: CEType -> Rep CEType x #

to :: Rep CEType x -> CEType #

Hashable CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

hashWithSalt :: Int -> CEType -> Int #

hash :: CEType -> Int #

ToJSON CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromJSON CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

ToQuery CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toBS :: CEType -> ByteString #

FromText CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

parser :: Parser CEType #

ToText CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toText :: CEType -> Text #

NFData CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: CEType -> () #

type Rep CEType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep CEType = D1 (MetaData "CEType" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "Managed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Unmanaged" PrefixI False) (U1 :: Type -> Type))

CRType

data CRType Source #

Constructors

EC2 
Spot 
Instances
Bounded CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

Data CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: CRType -> Constr #

dataTypeOf :: CRType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep CRType :: Type -> Type #

Methods

from :: CRType -> Rep CRType x #

to :: Rep CRType x -> CRType #

Hashable CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

hashWithSalt :: Int -> CRType -> Int #

hash :: CRType -> Int #

ToJSON CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromJSON CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

ToQuery CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toBS :: CRType -> ByteString #

FromText CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

parser :: Parser CRType #

ToText CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toText :: CRType -> Text #

NFData CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: CRType -> () #

type Rep CRType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep CRType = D1 (MetaData "CRType" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "EC2" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Spot" PrefixI False) (U1 :: Type -> Type))

JQState

data JQState Source #

Constructors

JQSDisabled 
JQSEnabled 
Instances
Bounded JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

Data JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: JQState -> Constr #

dataTypeOf :: JQState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep JQState :: Type -> Type #

Methods

from :: JQState -> Rep JQState x #

to :: Rep JQState x -> JQState #

Hashable JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

hashWithSalt :: Int -> JQState -> Int #

hash :: JQState -> Int #

ToJSON JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromJSON JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

ToQuery JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toBS :: JQState -> ByteString #

FromText JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToText JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toText :: JQState -> Text #

NFData JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: JQState -> () #

type Rep JQState Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep JQState = D1 (MetaData "JQState" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "JQSDisabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JQSEnabled" PrefixI False) (U1 :: Type -> Type))

JQStatus

data JQStatus Source #

Instances
Bounded JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Data JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: JQStatus -> Constr #

dataTypeOf :: JQStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep JQStatus :: Type -> Type #

Methods

from :: JQStatus -> Rep JQStatus x #

to :: Rep JQStatus x -> JQStatus #

Hashable JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

hashWithSalt :: Int -> JQStatus -> Int #

hash :: JQStatus -> Int #

FromJSON JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

ToQuery JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toBS :: JQStatus -> ByteString #

FromText JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToText JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toText :: JQStatus -> Text #

NFData JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: JQStatus -> () #

type Rep JQStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep JQStatus = D1 (MetaData "JQStatus" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) ((C1 (MetaCons "Creating" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Deleted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Deleting" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Invalid" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Updating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Valid" PrefixI False) (U1 :: Type -> Type))))

JobDefinitionType

data JobDefinitionType Source #

Constructors

Container 
Instances
Bounded JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Data JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: JobDefinitionType -> Constr #

dataTypeOf :: JobDefinitionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep JobDefinitionType :: Type -> Type #

Hashable JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToJSON JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToQuery JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromText JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToText JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

NFData JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: JobDefinitionType -> () #

type Rep JobDefinitionType Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep JobDefinitionType = D1 (MetaData "JobDefinitionType" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "Container" PrefixI False) (U1 :: Type -> Type))

JobStatus

data JobStatus Source #

Instances
Bounded JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Enum JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Eq JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Data JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

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

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

toConstr :: JobStatus -> Constr #

dataTypeOf :: JobStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Read JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Show JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Generic JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Associated Types

type Rep JobStatus :: Type -> Type #

Hashable JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToJSON JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

FromJSON JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToHeader JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToQuery JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToByteString JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toBS :: JobStatus -> ByteString #

FromText JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

ToText JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

toText :: JobStatus -> Text #

NFData JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

Methods

rnf :: JobStatus -> () #

type Rep JobStatus Source # 
Instance details

Defined in Network.AWS.Batch.Types.Sum

type Rep JobStatus = D1 (MetaData "JobStatus" "Network.AWS.Batch.Types.Sum" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) ((C1 (MetaCons "Failed" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Pending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Runnable" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Running" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Starting" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Submitted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Succeeded" PrefixI False) (U1 :: Type -> Type))))

ArrayProperties

data ArrayProperties Source #

An object representing an AWS Batch array job.

See: arrayProperties smart constructor.

Instances
Eq ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ArrayProperties -> Constr #

dataTypeOf :: ArrayProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ArrayProperties :: Type -> Type #

Hashable ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ArrayProperties -> () #

type Rep ArrayProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ArrayProperties = D1 (MetaData "ArrayProperties" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" True) (C1 (MetaCons "ArrayProperties'" PrefixI True) (S1 (MetaSel (Just "_apSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))

arrayProperties :: ArrayProperties Source #

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

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

  • apSize - The size of the array job.

apSize :: Lens' ArrayProperties (Maybe Int) Source #

The size of the array job.

ArrayPropertiesDetail

data ArrayPropertiesDetail Source #

An object representing the array properties of a job.

See: arrayPropertiesDetail smart constructor.

Instances
Eq ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ArrayPropertiesDetail -> Constr #

dataTypeOf :: ArrayPropertiesDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ArrayPropertiesDetail :: Type -> Type #

Hashable ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ArrayPropertiesDetail -> () #

type Rep ArrayPropertiesDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ArrayPropertiesDetail = D1 (MetaData "ArrayPropertiesDetail" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ArrayPropertiesDetail'" PrefixI True) (S1 (MetaSel (Just "_apdSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_apdStatusSummary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Int))) :*: S1 (MetaSel (Just "_apdIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))

arrayPropertiesDetail :: ArrayPropertiesDetail Source #

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

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

  • apdSize - The size of the array job. This parameter is returned for parent array jobs.
  • apdStatusSummary - A summary of the number of array job children in each available job status. This parameter is returned for parent array jobs.
  • apdIndex - The job index within the array that is associated with this job. This parameter is returned for array job children.

apdSize :: Lens' ArrayPropertiesDetail (Maybe Int) Source #

The size of the array job. This parameter is returned for parent array jobs.

apdStatusSummary :: Lens' ArrayPropertiesDetail (HashMap Text Int) Source #

A summary of the number of array job children in each available job status. This parameter is returned for parent array jobs.

apdIndex :: Lens' ArrayPropertiesDetail (Maybe Int) Source #

The job index within the array that is associated with this job. This parameter is returned for array job children.

ArrayPropertiesSummary

data ArrayPropertiesSummary Source #

An object representing the array properties of a job.

See: arrayPropertiesSummary smart constructor.

Instances
Eq ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ArrayPropertiesSummary -> Constr #

dataTypeOf :: ArrayPropertiesSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ArrayPropertiesSummary :: Type -> Type #

Hashable ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ArrayPropertiesSummary -> () #

type Rep ArrayPropertiesSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ArrayPropertiesSummary = D1 (MetaData "ArrayPropertiesSummary" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ArrayPropertiesSummary'" PrefixI True) (S1 (MetaSel (Just "_apsSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_apsIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))

arrayPropertiesSummary :: ArrayPropertiesSummary Source #

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

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

  • apsSize - The size of the array job. This parameter is returned for parent array jobs.
  • apsIndex - The job index within the array that is associated with this job. This parameter is returned for children of array jobs.

apsSize :: Lens' ArrayPropertiesSummary (Maybe Int) Source #

The size of the array job. This parameter is returned for parent array jobs.

apsIndex :: Lens' ArrayPropertiesSummary (Maybe Int) Source #

The job index within the array that is associated with this job. This parameter is returned for children of array jobs.

AttemptContainerDetail

data AttemptContainerDetail Source #

An object representing the details of a container that is part of a job attempt.

See: attemptContainerDetail smart constructor.

Instances
Eq AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: AttemptContainerDetail -> Constr #

dataTypeOf :: AttemptContainerDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep AttemptContainerDetail :: Type -> Type #

Hashable AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: AttemptContainerDetail -> () #

type Rep AttemptContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep AttemptContainerDetail = D1 (MetaData "AttemptContainerDetail" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "AttemptContainerDetail'" PrefixI True) ((S1 (MetaSel (Just "_acdTaskARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_acdContainerInstanceARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_acdReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_acdLogStreamName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_acdExitCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))

attemptContainerDetail :: AttemptContainerDetail Source #

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

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

  • acdTaskARN - The Amazon Resource Name (ARN) of the Amazon ECS task that is associated with the job attempt. Each container attempt receives a task ARN when they reach the STARTING status.
  • acdContainerInstanceARN - The Amazon Resource Name (ARN) of the Amazon ECS container instance that hosts the job attempt.
  • acdReason - A short (255 max characters) human-readable string to provide additional details about a running or stopped container.
  • acdLogStreamName - The name of the CloudWatch Logs log stream associated with the container. The log group for AWS Batch jobs is awsbatch/job . Each container attempt receives a log stream name when they reach the RUNNING status.
  • acdExitCode - The exit code for the job attempt. A non-zero exit code is considered a failure.

acdTaskARN :: Lens' AttemptContainerDetail (Maybe Text) Source #

The Amazon Resource Name (ARN) of the Amazon ECS task that is associated with the job attempt. Each container attempt receives a task ARN when they reach the STARTING status.

acdContainerInstanceARN :: Lens' AttemptContainerDetail (Maybe Text) Source #

The Amazon Resource Name (ARN) of the Amazon ECS container instance that hosts the job attempt.

acdReason :: Lens' AttemptContainerDetail (Maybe Text) Source #

A short (255 max characters) human-readable string to provide additional details about a running or stopped container.

acdLogStreamName :: Lens' AttemptContainerDetail (Maybe Text) Source #

The name of the CloudWatch Logs log stream associated with the container. The log group for AWS Batch jobs is awsbatch/job . Each container attempt receives a log stream name when they reach the RUNNING status.

acdExitCode :: Lens' AttemptContainerDetail (Maybe Int) Source #

The exit code for the job attempt. A non-zero exit code is considered a failure.

AttemptDetail

data AttemptDetail Source #

An object representing a job attempt.

See: attemptDetail smart constructor.

Instances
Eq AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: AttemptDetail -> Constr #

dataTypeOf :: AttemptDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep AttemptDetail :: Type -> Type #

Hashable AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: AttemptDetail -> () #

type Rep AttemptDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep AttemptDetail = D1 (MetaData "AttemptDetail" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "AttemptDetail'" PrefixI True) ((S1 (MetaSel (Just "_adStoppedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_adStartedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))) :*: (S1 (MetaSel (Just "_adContainer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AttemptContainerDetail)) :*: S1 (MetaSel (Just "_adStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

attemptDetail :: AttemptDetail Source #

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

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

  • adStoppedAt - The Unix time stamp (in seconds and milliseconds) for when the attempt was stopped (when the attempt transitioned from the RUNNING state to a terminal state, such as SUCCEEDED or FAILED ).
  • adStartedAt - The Unix time stamp (in seconds and milliseconds) for when the attempt was started (when the attempt transitioned from the STARTING state to the RUNNING state).
  • adContainer - Details about the container in this job attempt.
  • adStatusReason - A short, human-readable string to provide additional details about the current status of the job attempt.

adStoppedAt :: Lens' AttemptDetail (Maybe Integer) Source #

The Unix time stamp (in seconds and milliseconds) for when the attempt was stopped (when the attempt transitioned from the RUNNING state to a terminal state, such as SUCCEEDED or FAILED ).

adStartedAt :: Lens' AttemptDetail (Maybe Integer) Source #

The Unix time stamp (in seconds and milliseconds) for when the attempt was started (when the attempt transitioned from the STARTING state to the RUNNING state).

adContainer :: Lens' AttemptDetail (Maybe AttemptContainerDetail) Source #

Details about the container in this job attempt.

adStatusReason :: Lens' AttemptDetail (Maybe Text) Source #

A short, human-readable string to provide additional details about the current status of the job attempt.

ComputeEnvironmentDetail

data ComputeEnvironmentDetail Source #

An object representing an AWS Batch compute environment.

See: computeEnvironmentDetail smart constructor.

Instances
Eq ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ComputeEnvironmentDetail -> Constr #

dataTypeOf :: ComputeEnvironmentDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ComputeEnvironmentDetail :: Type -> Type #

Hashable ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ComputeEnvironmentDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ComputeEnvironmentDetail = D1 (MetaData "ComputeEnvironmentDetail" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ComputeEnvironmentDetail'" PrefixI True) (((S1 (MetaSel (Just "_cedStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CEStatus)) :*: S1 (MetaSel (Just "_cedState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CEState))) :*: (S1 (MetaSel (Just "_cedComputeResources") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ComputeResource)) :*: S1 (MetaSel (Just "_cedStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_cedType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CEType)) :*: S1 (MetaSel (Just "_cedServiceRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_cedComputeEnvironmentName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_cedComputeEnvironmentARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_cedEcsClusterARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))))

computeEnvironmentDetail Source #

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

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

  • cedStatus - The current status of the compute environment (for example, CREATING or VALID ).
  • cedState - The state of the compute environment. The valid values are ENABLED or DISABLED . An ENABLED state indicates that you can register instances with the compute environment and that the associated instances can accept jobs.
  • cedComputeResources - The compute resources defined for the compute environment.
  • cedStatusReason - A short, human-readable string to provide additional details about the current status of the compute environment.
  • cedType - The type of the compute environment.
  • cedServiceRole - The service role associated with the compute environment that allows AWS Batch to make calls to AWS API operations on your behalf.
  • cedComputeEnvironmentName - The name of the compute environment.
  • cedComputeEnvironmentARN - The Amazon Resource Name (ARN) of the compute environment.
  • cedEcsClusterARN - The Amazon Resource Name (ARN) of the underlying Amazon ECS cluster used by the compute environment.

cedStatus :: Lens' ComputeEnvironmentDetail (Maybe CEStatus) Source #

The current status of the compute environment (for example, CREATING or VALID ).

cedState :: Lens' ComputeEnvironmentDetail (Maybe CEState) Source #

The state of the compute environment. The valid values are ENABLED or DISABLED . An ENABLED state indicates that you can register instances with the compute environment and that the associated instances can accept jobs.

cedComputeResources :: Lens' ComputeEnvironmentDetail (Maybe ComputeResource) Source #

The compute resources defined for the compute environment.

cedStatusReason :: Lens' ComputeEnvironmentDetail (Maybe Text) Source #

A short, human-readable string to provide additional details about the current status of the compute environment.

cedType :: Lens' ComputeEnvironmentDetail (Maybe CEType) Source #

The type of the compute environment.

cedServiceRole :: Lens' ComputeEnvironmentDetail (Maybe Text) Source #

The service role associated with the compute environment that allows AWS Batch to make calls to AWS API operations on your behalf.

cedComputeEnvironmentName :: Lens' ComputeEnvironmentDetail Text Source #

The name of the compute environment.

cedComputeEnvironmentARN :: Lens' ComputeEnvironmentDetail Text Source #

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

cedEcsClusterARN :: Lens' ComputeEnvironmentDetail Text Source #

The Amazon Resource Name (ARN) of the underlying Amazon ECS cluster used by the compute environment.

ComputeEnvironmentOrder

data ComputeEnvironmentOrder Source #

The order in which compute environments are tried for job placement within a queue. Compute environments are tried in ascending order. For example, if two compute environments are associated with a job queue, the compute environment with a lower order integer value is tried for job placement first.

See: computeEnvironmentOrder smart constructor.

Instances
Eq ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ComputeEnvironmentOrder -> Constr #

dataTypeOf :: ComputeEnvironmentOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ComputeEnvironmentOrder :: Type -> Type #

Hashable ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ComputeEnvironmentOrder -> () #

type Rep ComputeEnvironmentOrder Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ComputeEnvironmentOrder = D1 (MetaData "ComputeEnvironmentOrder" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ComputeEnvironmentOrder'" PrefixI True) (S1 (MetaSel (Just "_ceoOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_ceoComputeEnvironment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

computeEnvironmentOrder Source #

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

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

ceoOrder :: Lens' ComputeEnvironmentOrder Int Source #

The order of the compute environment.

ceoComputeEnvironment :: Lens' ComputeEnvironmentOrder Text Source #

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

ComputeResource

data ComputeResource Source #

An object representing an AWS Batch compute resource.

See: computeResource smart constructor.

Instances
Eq ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ComputeResource -> Constr #

dataTypeOf :: ComputeResource -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ComputeResource :: Type -> Type #

Hashable ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ComputeResource -> () #

type Rep ComputeResource Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ComputeResource = D1 (MetaData "ComputeResource" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ComputeResource'" PrefixI True) (((S1 (MetaSel (Just "_crEc2KeyPair") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_crBidPercentage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_crSpotIAMFleetRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_crImageId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_crDesiredvCPUs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_crTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))))) :*: ((S1 (MetaSel (Just "_crType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CRType) :*: (S1 (MetaSel (Just "_crMinvCPUs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_crMaxvCPUs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) :*: ((S1 (MetaSel (Just "_crInstanceTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Just "_crSubnets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text])) :*: (S1 (MetaSel (Just "_crSecurityGroupIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Just "_crInstanceRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))))

computeResource Source #

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

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

  • crEc2KeyPair - The EC2 key pair that is used for instances launched in the compute environment.
  • crBidPercentage - The minimum percentage that a Spot Instance price must be when compared with the On-Demand price for that instance type before instances are launched. For example, if your bid percentage is 20%, then the Spot price must be below 20% of the current On-Demand price for that EC2 instance.
  • crSpotIAMFleetRole - The Amazon Resource Name (ARN) of the Amazon EC2 Spot Fleet IAM role applied to a SPOT compute environment.
  • crImageId - The Amazon Machine Image (AMI) ID used for instances launched in the compute environment.
  • crDesiredvCPUs - The desired number of EC2 vCPUS in the compute environment.
  • crTags - Key-value pair tags to be applied to resources that are launched in the compute environment.
  • crType - The type of compute environment.
  • crMinvCPUs - The minimum number of EC2 vCPUs that an environment should maintain.
  • crMaxvCPUs - The maximum number of EC2 vCPUs that an environment can reach.
  • crInstanceTypes - The instances types that may be launched. You can specify instance families to launch any instance type within those families (for example, c4 or p3 ), or you can specify specific sizes within a family (such as c4.8xlarge ). You can also choose optimal to pick instance types (from the latest C, M, and R instance families) on the fly that match the demand of your job queues.
  • crSubnets - The VPC subnets into which the compute resources are launched.
  • crSecurityGroupIds - The EC2 security group that is associated with instances launched in the compute environment.
  • crInstanceRole - The Amazon ECS instance profile applied to Amazon EC2 instances in a compute environment. You can specify the short name or full Amazon Resource Name (ARN) of an instance profile. For example, ecsInstanceRole or arn:aws:iam::aws_account_id:instance-profile/ecsInstanceRole . For more information, see Amazon ECS Instance Role in the AWS Batch User Guide .

crEc2KeyPair :: Lens' ComputeResource (Maybe Text) Source #

The EC2 key pair that is used for instances launched in the compute environment.

crBidPercentage :: Lens' ComputeResource (Maybe Int) Source #

The minimum percentage that a Spot Instance price must be when compared with the On-Demand price for that instance type before instances are launched. For example, if your bid percentage is 20%, then the Spot price must be below 20% of the current On-Demand price for that EC2 instance.

crSpotIAMFleetRole :: Lens' ComputeResource (Maybe Text) Source #

The Amazon Resource Name (ARN) of the Amazon EC2 Spot Fleet IAM role applied to a SPOT compute environment.

crImageId :: Lens' ComputeResource (Maybe Text) Source #

The Amazon Machine Image (AMI) ID used for instances launched in the compute environment.

crDesiredvCPUs :: Lens' ComputeResource (Maybe Int) Source #

The desired number of EC2 vCPUS in the compute environment.

crTags :: Lens' ComputeResource (HashMap Text Text) Source #

Key-value pair tags to be applied to resources that are launched in the compute environment.

crType :: Lens' ComputeResource CRType Source #

The type of compute environment.

crMinvCPUs :: Lens' ComputeResource Int Source #

The minimum number of EC2 vCPUs that an environment should maintain.

crMaxvCPUs :: Lens' ComputeResource Int Source #

The maximum number of EC2 vCPUs that an environment can reach.

crInstanceTypes :: Lens' ComputeResource [Text] Source #

The instances types that may be launched. You can specify instance families to launch any instance type within those families (for example, c4 or p3 ), or you can specify specific sizes within a family (such as c4.8xlarge ). You can also choose optimal to pick instance types (from the latest C, M, and R instance families) on the fly that match the demand of your job queues.

crSubnets :: Lens' ComputeResource [Text] Source #

The VPC subnets into which the compute resources are launched.

crSecurityGroupIds :: Lens' ComputeResource [Text] Source #

The EC2 security group that is associated with instances launched in the compute environment.

crInstanceRole :: Lens' ComputeResource Text Source #

The Amazon ECS instance profile applied to Amazon EC2 instances in a compute environment. You can specify the short name or full Amazon Resource Name (ARN) of an instance profile. For example, ecsInstanceRole or arn:aws:iam::aws_account_id:instance-profile/ecsInstanceRole . For more information, see Amazon ECS Instance Role in the AWS Batch User Guide .

ComputeResourceUpdate

data ComputeResourceUpdate Source #

An object representing the attributes of a compute environment that can be updated.

See: computeResourceUpdate smart constructor.

Instances
Eq ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ComputeResourceUpdate -> Constr #

dataTypeOf :: ComputeResourceUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ComputeResourceUpdate :: Type -> Type #

Hashable ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ComputeResourceUpdate -> () #

type Rep ComputeResourceUpdate Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ComputeResourceUpdate = D1 (MetaData "ComputeResourceUpdate" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ComputeResourceUpdate'" PrefixI True) (S1 (MetaSel (Just "_cruMinvCPUs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_cruMaxvCPUs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_cruDesiredvCPUs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))

computeResourceUpdate :: ComputeResourceUpdate Source #

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

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

  • cruMinvCPUs - The minimum number of EC2 vCPUs that an environment should maintain.
  • cruMaxvCPUs - The maximum number of EC2 vCPUs that an environment can reach.
  • cruDesiredvCPUs - The desired number of EC2 vCPUS in the compute environment.

cruMinvCPUs :: Lens' ComputeResourceUpdate (Maybe Int) Source #

The minimum number of EC2 vCPUs that an environment should maintain.

cruMaxvCPUs :: Lens' ComputeResourceUpdate (Maybe Int) Source #

The maximum number of EC2 vCPUs that an environment can reach.

cruDesiredvCPUs :: Lens' ComputeResourceUpdate (Maybe Int) Source #

The desired number of EC2 vCPUS in the compute environment.

ContainerDetail

data ContainerDetail Source #

An object representing the details of a container that is part of a job.

See: containerDetail smart constructor.

Instances
Eq ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ContainerDetail -> Constr #

dataTypeOf :: ContainerDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ContainerDetail :: Type -> Type #

Hashable ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ContainerDetail -> () #

type Rep ContainerDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ContainerDetail = D1 (MetaData "ContainerDetail" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ContainerDetail'" PrefixI True) ((((S1 (MetaSel (Just "_cdImage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cdCommand") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) :*: (S1 (MetaSel (Just "_cdEnvironment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [KeyValuePair])) :*: S1 (MetaSel (Just "_cdTaskARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_cdUlimits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Ulimit])) :*: S1 (MetaSel (Just "_cdContainerInstanceARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_cdPrivileged") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_cdJobRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: (((S1 (MetaSel (Just "_cdMemory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_cdUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_cdReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cdLogStreamName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_cdMountPoints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MountPoint])) :*: S1 (MetaSel (Just "_cdExitCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 (MetaSel (Just "_cdVcpus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_cdReadonlyRootFilesystem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_cdVolumes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Volume]))))))))

containerDetail :: ContainerDetail Source #

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

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

  • cdImage - The image used to start the container.
  • cdCommand - The command that is passed to the container.
  • cdEnvironment - The environment variables to pass to a container.
  • cdTaskARN - The Amazon Resource Name (ARN) of the Amazon ECS task that is associated with the container job. Each container attempt receives a task ARN when they reach the STARTING status.
  • cdUlimits - A list of ulimit values to set in the container.
  • cdContainerInstanceARN - The Amazon Resource Name (ARN) of the container instance on which the container is running.
  • cdPrivileged - When this parameter is true, the container is given elevated privileges on the host container instance (similar to the root user).
  • cdJobRoleARN - The Amazon Resource Name (ARN) associated with the job upon execution.
  • cdMemory - The number of MiB of memory reserved for the job.
  • cdUser - The user name to use inside the container.
  • cdReason - A short (255 max characters) human-readable string to provide additional details about a running or stopped container.
  • cdLogStreamName - The name of the CloudWatch Logs log stream associated with the container. The log group for AWS Batch jobs is awsbatch/job . Each container attempt receives a log stream name when they reach the RUNNING status.
  • cdMountPoints - The mount points for data volumes in your container.
  • cdExitCode - The exit code to return upon completion.
  • cdVcpus - The number of VCPUs allocated for the job.
  • cdReadonlyRootFilesystem - When this parameter is true, the container is given read-only access to its root file system.
  • cdVolumes - A list of volumes associated with the job.

cdImage :: Lens' ContainerDetail (Maybe Text) Source #

The image used to start the container.

cdCommand :: Lens' ContainerDetail [Text] Source #

The command that is passed to the container.

cdEnvironment :: Lens' ContainerDetail [KeyValuePair] Source #

The environment variables to pass to a container.

cdTaskARN :: Lens' ContainerDetail (Maybe Text) Source #

The Amazon Resource Name (ARN) of the Amazon ECS task that is associated with the container job. Each container attempt receives a task ARN when they reach the STARTING status.

cdUlimits :: Lens' ContainerDetail [Ulimit] Source #

A list of ulimit values to set in the container.

cdContainerInstanceARN :: Lens' ContainerDetail (Maybe Text) Source #

The Amazon Resource Name (ARN) of the container instance on which the container is running.

cdPrivileged :: Lens' ContainerDetail (Maybe Bool) Source #

When this parameter is true, the container is given elevated privileges on the host container instance (similar to the root user).

cdJobRoleARN :: Lens' ContainerDetail (Maybe Text) Source #

The Amazon Resource Name (ARN) associated with the job upon execution.

cdMemory :: Lens' ContainerDetail (Maybe Int) Source #

The number of MiB of memory reserved for the job.

cdUser :: Lens' ContainerDetail (Maybe Text) Source #

The user name to use inside the container.

cdReason :: Lens' ContainerDetail (Maybe Text) Source #

A short (255 max characters) human-readable string to provide additional details about a running or stopped container.

cdLogStreamName :: Lens' ContainerDetail (Maybe Text) Source #

The name of the CloudWatch Logs log stream associated with the container. The log group for AWS Batch jobs is awsbatch/job . Each container attempt receives a log stream name when they reach the RUNNING status.

cdMountPoints :: Lens' ContainerDetail [MountPoint] Source #

The mount points for data volumes in your container.

cdExitCode :: Lens' ContainerDetail (Maybe Int) Source #

The exit code to return upon completion.

cdVcpus :: Lens' ContainerDetail (Maybe Int) Source #

The number of VCPUs allocated for the job.

cdReadonlyRootFilesystem :: Lens' ContainerDetail (Maybe Bool) Source #

When this parameter is true, the container is given read-only access to its root file system.

cdVolumes :: Lens' ContainerDetail [Volume] Source #

A list of volumes associated with the job.

ContainerOverrides

data ContainerOverrides Source #

The overrides that should be sent to a container.

See: containerOverrides smart constructor.

Instances
Eq ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ContainerOverrides -> Constr #

dataTypeOf :: ContainerOverrides -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ContainerOverrides :: Type -> Type #

Hashable ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ContainerOverrides -> () #

type Rep ContainerOverrides Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ContainerOverrides = D1 (MetaData "ContainerOverrides" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ContainerOverrides'" PrefixI True) ((S1 (MetaSel (Just "_coCommand") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_coEnvironment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [KeyValuePair]))) :*: (S1 (MetaSel (Just "_coMemory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_coVcpus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))

containerOverrides :: ContainerOverrides Source #

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

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

  • coCommand - The command to send to the container that overrides the default command from the Docker image or the job definition.
  • coEnvironment - The environment variables to send to the container. You can add new environment variables, which are added to the container at launch, or you can override the existing environment variables from the Docker image or the job definition.
  • coMemory - The number of MiB of memory reserved for the job. This value overrides the value set in the job definition.
  • coVcpus - The number of vCPUs to reserve for the container. This value overrides the value set in the job definition.

coCommand :: Lens' ContainerOverrides [Text] Source #

The command to send to the container that overrides the default command from the Docker image or the job definition.

coEnvironment :: Lens' ContainerOverrides [KeyValuePair] Source #

The environment variables to send to the container. You can add new environment variables, which are added to the container at launch, or you can override the existing environment variables from the Docker image or the job definition.

coMemory :: Lens' ContainerOverrides (Maybe Int) Source #

The number of MiB of memory reserved for the job. This value overrides the value set in the job definition.

coVcpus :: Lens' ContainerOverrides (Maybe Int) Source #

The number of vCPUs to reserve for the container. This value overrides the value set in the job definition.

ContainerProperties

data ContainerProperties Source #

Container properties are used in job definitions to describe the container that is launched as part of a job.

See: containerProperties smart constructor.

Instances
Eq ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ContainerProperties -> Constr #

dataTypeOf :: ContainerProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ContainerProperties :: Type -> Type #

Hashable ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ContainerProperties -> () #

type Rep ContainerProperties Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ContainerProperties = D1 (MetaData "ContainerProperties" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ContainerProperties'" PrefixI True) (((S1 (MetaSel (Just "_cpCommand") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 (MetaSel (Just "_cpEnvironment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [KeyValuePair])) :*: S1 (MetaSel (Just "_cpUlimits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Ulimit])))) :*: (S1 (MetaSel (Just "_cpPrivileged") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_cpJobRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cpUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: ((S1 (MetaSel (Just "_cpMountPoints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MountPoint])) :*: (S1 (MetaSel (Just "_cpReadonlyRootFilesystem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_cpVolumes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Volume])))) :*: (S1 (MetaSel (Just "_cpImage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_cpVcpus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_cpMemory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))))

containerProperties Source #

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

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

  • cpCommand - The command that is passed to the container. This parameter maps to Cmd in the Create a container section of the Docker Remote API and the COMMAND parameter to docker run . For more information, see https://docs.docker.com/engine/reference/builder/#cmd .
  • cpEnvironment - The environment variables to pass to a container. This parameter maps to Env in the Create a container section of the Docker Remote API and the --env option to docker run . Important: We do not recommend using plaintext environment variables for sensitive information, such as credential data.
  • cpUlimits - A list of ulimits to set in the container. This parameter maps to Ulimits in the Create a container section of the Docker Remote API and the --ulimit option to docker run .
  • cpPrivileged - When this parameter is true, the container is given elevated privileges on the host container instance (similar to the root user). This parameter maps to Privileged in the Create a container section of the Docker Remote API and the --privileged option to docker run .
  • cpJobRoleARN - The Amazon Resource Name (ARN) of the IAM role that the container can assume for AWS permissions.
  • cpUser - The user name to use inside the container. This parameter maps to User in the Create a container section of the Docker Remote API and the --user option to docker run .
  • cpMountPoints - The mount points for data volumes in your container. This parameter maps to Volumes in the Create a container section of the Docker Remote API and the --volume option to docker run .
  • cpReadonlyRootFilesystem - When this parameter is true, the container is given read-only access to its root file system. This parameter maps to ReadonlyRootfs in the Create a container section of the Docker Remote API and the --read-only option to docker run .
  • cpVolumes - A list of data volumes used in a job.
  • cpImage - The image used to start a container. This string is passed directly to the Docker daemon. Images in the Docker Hub registry are available by default. Other repositories are specified with repository-url /image :tag . Up to 255 letters (uppercase and lowercase), numbers, hyphens, underscores, colons, periods, forward slashes, and number signs are allowed. This parameter maps to Image in the Create a container section of the Docker Remote API and the IMAGE parameter of docker run . * Images in Amazon ECR repositories use the full registry and repository URI (for example, 012345678910.dkr.ecr.region-name.amazonaws.com/repository-name ). * Images in official repositories on Docker Hub use a single name (for example, ubuntu or mongo ). * Images in other repositories on Docker Hub are qualified with an organization name (for example, amazon/amazon-ecs-agent ). * Images in other online repositories are qualified further by a domain name (for example, quay.ioassemblylineubuntu ).
  • cpVcpus - The number of vCPUs reserved for the container. This parameter maps to CpuShares in the Create a container section of the Docker Remote API and the --cpu-shares option to docker run . Each vCPU is equivalent to 1,024 CPU shares. You must specify at least one vCPU.
  • cpMemory - The hard limit (in MiB) of memory to present to the container. If your container attempts to exceed the memory specified here, the container is killed. This parameter maps to Memory in the Create a container section of the Docker Remote API and the --memory option to docker run . You must specify at least 4 MiB of memory for a job.

cpCommand :: Lens' ContainerProperties [Text] Source #

The command that is passed to the container. This parameter maps to Cmd in the Create a container section of the Docker Remote API and the COMMAND parameter to docker run . For more information, see https://docs.docker.com/engine/reference/builder/#cmd .

cpEnvironment :: Lens' ContainerProperties [KeyValuePair] Source #

The environment variables to pass to a container. This parameter maps to Env in the Create a container section of the Docker Remote API and the --env option to docker run . Important: We do not recommend using plaintext environment variables for sensitive information, such as credential data.

cpUlimits :: Lens' ContainerProperties [Ulimit] Source #

A list of ulimits to set in the container. This parameter maps to Ulimits in the Create a container section of the Docker Remote API and the --ulimit option to docker run .

cpPrivileged :: Lens' ContainerProperties (Maybe Bool) Source #

When this parameter is true, the container is given elevated privileges on the host container instance (similar to the root user). This parameter maps to Privileged in the Create a container section of the Docker Remote API and the --privileged option to docker run .

cpJobRoleARN :: Lens' ContainerProperties (Maybe Text) Source #

The Amazon Resource Name (ARN) of the IAM role that the container can assume for AWS permissions.

cpUser :: Lens' ContainerProperties (Maybe Text) Source #

The user name to use inside the container. This parameter maps to User in the Create a container section of the Docker Remote API and the --user option to docker run .

cpMountPoints :: Lens' ContainerProperties [MountPoint] Source #

The mount points for data volumes in your container. This parameter maps to Volumes in the Create a container section of the Docker Remote API and the --volume option to docker run .

cpReadonlyRootFilesystem :: Lens' ContainerProperties (Maybe Bool) Source #

When this parameter is true, the container is given read-only access to its root file system. This parameter maps to ReadonlyRootfs in the Create a container section of the Docker Remote API and the --read-only option to docker run .

cpVolumes :: Lens' ContainerProperties [Volume] Source #

A list of data volumes used in a job.

cpImage :: Lens' ContainerProperties Text Source #

The image used to start a container. This string is passed directly to the Docker daemon. Images in the Docker Hub registry are available by default. Other repositories are specified with repository-url /image :tag . Up to 255 letters (uppercase and lowercase), numbers, hyphens, underscores, colons, periods, forward slashes, and number signs are allowed. This parameter maps to Image in the Create a container section of the Docker Remote API and the IMAGE parameter of docker run . * Images in Amazon ECR repositories use the full registry and repository URI (for example, 012345678910.dkr.ecr.region-name.amazonaws.com/repository-name ). * Images in official repositories on Docker Hub use a single name (for example, ubuntu or mongo ). * Images in other repositories on Docker Hub are qualified with an organization name (for example, amazon/amazon-ecs-agent ). * Images in other online repositories are qualified further by a domain name (for example, quay.ioassemblylineubuntu ).

cpVcpus :: Lens' ContainerProperties Int Source #

The number of vCPUs reserved for the container. This parameter maps to CpuShares in the Create a container section of the Docker Remote API and the --cpu-shares option to docker run . Each vCPU is equivalent to 1,024 CPU shares. You must specify at least one vCPU.

cpMemory :: Lens' ContainerProperties Int Source #

The hard limit (in MiB) of memory to present to the container. If your container attempts to exceed the memory specified here, the container is killed. This parameter maps to Memory in the Create a container section of the Docker Remote API and the --memory option to docker run . You must specify at least 4 MiB of memory for a job.

ContainerSummary

data ContainerSummary Source #

An object representing summary details of a container within a job.

See: containerSummary smart constructor.

Instances
Eq ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: ContainerSummary -> Constr #

dataTypeOf :: ContainerSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep ContainerSummary :: Type -> Type #

Hashable ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: ContainerSummary -> () #

type Rep ContainerSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep ContainerSummary = D1 (MetaData "ContainerSummary" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "ContainerSummary'" PrefixI True) (S1 (MetaSel (Just "_csReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_csExitCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))

containerSummary :: ContainerSummary Source #

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

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

  • csReason - A short (255 max characters) human-readable string to provide additional details about a running or stopped container.
  • csExitCode - The exit code to return upon completion.

csReason :: Lens' ContainerSummary (Maybe Text) Source #

A short (255 max characters) human-readable string to provide additional details about a running or stopped container.

csExitCode :: Lens' ContainerSummary (Maybe Int) Source #

The exit code to return upon completion.

Host

data Host Source #

The contents of the host parameter determine whether your data volume persists on the host container instance and where it is stored. If the host parameter is empty, then the Docker daemon assigns a host path for your data volume, but the data is not guaranteed to persist after the containers associated with it stop running.

See: host smart constructor.

Instances
Eq Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

Data Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: Host -> Constr #

dataTypeOf :: Host -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Generic Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep Host :: Type -> Type #

Methods

from :: Host -> Rep Host x #

to :: Rep Host x -> Host #

Hashable Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

hashWithSalt :: Int -> Host -> Int #

hash :: Host -> Int #

ToJSON Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: Host -> () #

type Rep Host Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep Host = D1 (MetaData "Host" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" True) (C1 (MetaCons "Host'" PrefixI True) (S1 (MetaSel (Just "_hSourcePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

host :: Host Source #

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

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

  • hSourcePath - The path on the host container instance that is presented to the container. If this parameter is empty, then the Docker daemon has assigned a host path for you. If the host parameter contains a sourcePath file location, then the data volume persists at the specified location on the host container instance until you delete it manually. If the sourcePath value does not exist on the host container instance, the Docker daemon creates it. If the location does exist, the contents of the source path folder are exported.

hSourcePath :: Lens' Host (Maybe Text) Source #

The path on the host container instance that is presented to the container. If this parameter is empty, then the Docker daemon has assigned a host path for you. If the host parameter contains a sourcePath file location, then the data volume persists at the specified location on the host container instance until you delete it manually. If the sourcePath value does not exist on the host container instance, the Docker daemon creates it. If the location does exist, the contents of the source path folder are exported.

JobDefinition

data JobDefinition Source #

An object representing an AWS Batch job definition.

See: jobDefinition smart constructor.

Instances
Eq JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: JobDefinition -> Constr #

dataTypeOf :: JobDefinition -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep JobDefinition :: Type -> Type #

Hashable JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: JobDefinition -> () #

type Rep JobDefinition Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

jobDefinition Source #

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

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

  • jddStatus - The status of the job definition.
  • jddRetryStrategy - The retry strategy to use for failed jobs that are submitted with this job definition.
  • jddParameters - Default parameters or parameter substitution placeholders that are set in the job definition. Parameters are specified as a key-value pair mapping. Parameters in a SubmitJob request override any corresponding parameter defaults from the job definition.
  • jddTimeout - The timeout configuration for jobs that are submitted with this job definition. You can specify a timeout duration after which AWS Batch terminates your jobs if they have not finished.
  • jddContainerProperties - An object with various properties specific to container-based jobs.
  • jddJobDefinitionName - The name of the job definition.
  • jddJobDefinitionARN - The Amazon Resource Name (ARN) for the job definition.
  • jddRevision - The revision of the job definition.
  • jddType - The type of job definition.

jddStatus :: Lens' JobDefinition (Maybe Text) Source #

The status of the job definition.

jddRetryStrategy :: Lens' JobDefinition (Maybe RetryStrategy) Source #

The retry strategy to use for failed jobs that are submitted with this job definition.

jddParameters :: Lens' JobDefinition (HashMap Text Text) Source #

Default parameters or parameter substitution placeholders that are set in the job definition. Parameters are specified as a key-value pair mapping. Parameters in a SubmitJob request override any corresponding parameter defaults from the job definition.

jddTimeout :: Lens' JobDefinition (Maybe JobTimeout) Source #

The timeout configuration for jobs that are submitted with this job definition. You can specify a timeout duration after which AWS Batch terminates your jobs if they have not finished.

jddContainerProperties :: Lens' JobDefinition (Maybe ContainerProperties) Source #

An object with various properties specific to container-based jobs.

jddJobDefinitionName :: Lens' JobDefinition Text Source #

The name of the job definition.

jddJobDefinitionARN :: Lens' JobDefinition Text Source #

The Amazon Resource Name (ARN) for the job definition.

jddRevision :: Lens' JobDefinition Int Source #

The revision of the job definition.

jddType :: Lens' JobDefinition Text Source #

The type of job definition.

JobDependency

data JobDependency Source #

An object representing an AWS Batch job dependency.

See: jobDependency smart constructor.

Instances
Eq JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: JobDependency -> Constr #

dataTypeOf :: JobDependency -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep JobDependency :: Type -> Type #

Hashable JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: JobDependency -> () #

type Rep JobDependency Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep JobDependency = D1 (MetaData "JobDependency" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "JobDependency'" PrefixI True) (S1 (MetaSel (Just "_jJobId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_jType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ArrayJobDependency))))

jobDependency :: JobDependency Source #

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

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

  • jJobId - The job ID of the AWS Batch job associated with this dependency.
  • jType - The type of the job dependency.

jJobId :: Lens' JobDependency (Maybe Text) Source #

The job ID of the AWS Batch job associated with this dependency.

jType :: Lens' JobDependency (Maybe ArrayJobDependency) Source #

The type of the job dependency.

JobDetail

data JobDetail Source #

An object representing an AWS Batch job.

See: jobDetail smart constructor.

Instances
Eq JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: JobDetail -> Constr #

dataTypeOf :: JobDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep JobDetail :: Type -> Type #

Hashable JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: JobDetail -> () #

type Rep JobDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep JobDetail = D1 (MetaData "JobDetail" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "JobDetail'" PrefixI True) ((((S1 (MetaSel (Just "_jdStoppedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_jdCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))) :*: (S1 (MetaSel (Just "_jdRetryStrategy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RetryStrategy)) :*: S1 (MetaSel (Just "_jdAttempts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AttemptDetail])))) :*: ((S1 (MetaSel (Just "_jdDependsOn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [JobDependency])) :*: S1 (MetaSel (Just "_jdContainer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ContainerDetail))) :*: (S1 (MetaSel (Just "_jdParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text))) :*: S1 (MetaSel (Just "_jdStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: (((S1 (MetaSel (Just "_jdArrayProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ArrayPropertiesDetail)) :*: S1 (MetaSel (Just "_jdTimeout") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JobTimeout))) :*: (S1 (MetaSel (Just "_jdJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_jdJobId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :*: ((S1 (MetaSel (Just "_jdJobQueue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_jdStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JobStatus)) :*: (S1 (MetaSel (Just "_jdStartedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Integer) :*: S1 (MetaSel (Just "_jdJobDefinition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))))

jobDetail Source #

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

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

  • jdStoppedAt - The Unix time stamp (in seconds and milliseconds) for when the job was stopped (when the job transitioned from the RUNNING state to a terminal state, such as SUCCEEDED or FAILED ).
  • jdCreatedAt - The Unix time stamp (in seconds and milliseconds) for when the job was created. For non-array jobs and parent array jobs, this is when the job entered the SUBMITTED state (at the time SubmitJob was called). For array child jobs, this is when the child job was spawned by its parent and entered the PENDING state.
  • jdRetryStrategy - The retry strategy to use for this job if an attempt fails.
  • jdAttempts - A list of job attempts associated with this job.
  • jdDependsOn - A list of job names or IDs on which this job depends.
  • jdContainer - An object representing the details of the container that is associated with the job.
  • jdParameters - Additional parameters passed to the job that replace parameter substitution placeholders or override any corresponding parameter defaults from the job definition.
  • jdStatusReason - A short, human-readable string to provide additional details about the current status of the job.
  • jdArrayProperties - The array properties of the job, if it is an array job.
  • jdTimeout - The timeout configuration for the job.
  • jdJobName - The name of the job.
  • jdJobId - The ID for the job.
  • jdJobQueue - The Amazon Resource Name (ARN) of the job queue with which the job is associated.
  • jdStatus - The current status for the job.
  • jdStartedAt - The Unix time stamp (in seconds and milliseconds) for when the job was started (when the job transitioned from the STARTING state to the RUNNING state).
  • jdJobDefinition - The job definition that is used by this job.

jdStoppedAt :: Lens' JobDetail (Maybe Integer) Source #

The Unix time stamp (in seconds and milliseconds) for when the job was stopped (when the job transitioned from the RUNNING state to a terminal state, such as SUCCEEDED or FAILED ).

jdCreatedAt :: Lens' JobDetail (Maybe Integer) Source #

The Unix time stamp (in seconds and milliseconds) for when the job was created. For non-array jobs and parent array jobs, this is when the job entered the SUBMITTED state (at the time SubmitJob was called). For array child jobs, this is when the child job was spawned by its parent and entered the PENDING state.

jdRetryStrategy :: Lens' JobDetail (Maybe RetryStrategy) Source #

The retry strategy to use for this job if an attempt fails.

jdAttempts :: Lens' JobDetail [AttemptDetail] Source #

A list of job attempts associated with this job.

jdDependsOn :: Lens' JobDetail [JobDependency] Source #

A list of job names or IDs on which this job depends.

jdContainer :: Lens' JobDetail (Maybe ContainerDetail) Source #

An object representing the details of the container that is associated with the job.

jdParameters :: Lens' JobDetail (HashMap Text Text) Source #

Additional parameters passed to the job that replace parameter substitution placeholders or override any corresponding parameter defaults from the job definition.

jdStatusReason :: Lens' JobDetail (Maybe Text) Source #

A short, human-readable string to provide additional details about the current status of the job.

jdArrayProperties :: Lens' JobDetail (Maybe ArrayPropertiesDetail) Source #

The array properties of the job, if it is an array job.

jdTimeout :: Lens' JobDetail (Maybe JobTimeout) Source #

The timeout configuration for the job.

jdJobName :: Lens' JobDetail Text Source #

The name of the job.

jdJobId :: Lens' JobDetail Text Source #

The ID for the job.

jdJobQueue :: Lens' JobDetail Text Source #

The Amazon Resource Name (ARN) of the job queue with which the job is associated.

jdStatus :: Lens' JobDetail JobStatus Source #

The current status for the job.

jdStartedAt :: Lens' JobDetail Integer Source #

The Unix time stamp (in seconds and milliseconds) for when the job was started (when the job transitioned from the STARTING state to the RUNNING state).

jdJobDefinition :: Lens' JobDetail Text Source #

The job definition that is used by this job.

JobQueueDetail

data JobQueueDetail Source #

An object representing the details of an AWS Batch job queue.

See: jobQueueDetail smart constructor.

Instances
Eq JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: JobQueueDetail -> Constr #

dataTypeOf :: JobQueueDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep JobQueueDetail :: Type -> Type #

Hashable JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: JobQueueDetail -> () #

type Rep JobQueueDetail Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep JobQueueDetail = D1 (MetaData "JobQueueDetail" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "JobQueueDetail'" PrefixI True) ((S1 (MetaSel (Just "_jqdStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JQStatus)) :*: (S1 (MetaSel (Just "_jqdStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_jqdJobQueueName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :*: ((S1 (MetaSel (Just "_jqdJobQueueARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_jqdState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JQState)) :*: (S1 (MetaSel (Just "_jqdPriority") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_jqdComputeEnvironmentOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ComputeEnvironmentOrder])))))

jobQueueDetail Source #

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

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

  • jqdStatus - The status of the job queue (for example, CREATING or VALID ).
  • jqdStatusReason - A short, human-readable string to provide additional details about the current status of the job queue.
  • jqdJobQueueName - The name of the job queue.
  • jqdJobQueueARN - The Amazon Resource Name (ARN) of the job queue.
  • jqdState - Describes the ability of the queue to accept new jobs.
  • jqdPriority - The priority of the job queue.
  • jqdComputeEnvironmentOrder - The compute environments that are attached to the job queue and the order in which job placement is preferred. Compute environments are selected for job placement in ascending order.

jqdStatus :: Lens' JobQueueDetail (Maybe JQStatus) Source #

The status of the job queue (for example, CREATING or VALID ).

jqdStatusReason :: Lens' JobQueueDetail (Maybe Text) Source #

A short, human-readable string to provide additional details about the current status of the job queue.

jqdJobQueueName :: Lens' JobQueueDetail Text Source #

The name of the job queue.

jqdJobQueueARN :: Lens' JobQueueDetail Text Source #

The Amazon Resource Name (ARN) of the job queue.

jqdState :: Lens' JobQueueDetail JQState Source #

Describes the ability of the queue to accept new jobs.

jqdPriority :: Lens' JobQueueDetail Int Source #

The priority of the job queue.

jqdComputeEnvironmentOrder :: Lens' JobQueueDetail [ComputeEnvironmentOrder] Source #

The compute environments that are attached to the job queue and the order in which job placement is preferred. Compute environments are selected for job placement in ascending order.

JobSummary

data JobSummary Source #

An object representing summary details of a job.

See: jobSummary smart constructor.

Instances
Eq JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: JobSummary -> Constr #

dataTypeOf :: JobSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep JobSummary :: Type -> Type #

Hashable JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: JobSummary -> () #

type Rep JobSummary Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

jobSummary Source #

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

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

  • jsStoppedAt - The Unix time stamp for when the job was stopped (when the job transitioned from the RUNNING state to a terminal state, such as SUCCEEDED or FAILED ).
  • jsStatus - The current status for the job.
  • jsCreatedAt - The Unix time stamp for when the job was created. For non-array jobs and parent array jobs, this is when the job entered the SUBMITTED state (at the time SubmitJob was called). For array child jobs, this is when the child job was spawned by its parent and entered the PENDING state.
  • jsStartedAt - The Unix time stamp for when the job was started (when the job transitioned from the STARTING state to the RUNNING state).
  • jsContainer - An object representing the details of the container that is associated with the job.
  • jsStatusReason - A short, human-readable string to provide additional details about the current status of the job.
  • jsArrayProperties - The array properties of the job, if it is an array job.
  • jsJobId - The ID of the job.
  • jsJobName - The name of the job.

jsStoppedAt :: Lens' JobSummary (Maybe Integer) Source #

The Unix time stamp for when the job was stopped (when the job transitioned from the RUNNING state to a terminal state, such as SUCCEEDED or FAILED ).

jsStatus :: Lens' JobSummary (Maybe JobStatus) Source #

The current status for the job.

jsCreatedAt :: Lens' JobSummary (Maybe Integer) Source #

The Unix time stamp for when the job was created. For non-array jobs and parent array jobs, this is when the job entered the SUBMITTED state (at the time SubmitJob was called). For array child jobs, this is when the child job was spawned by its parent and entered the PENDING state.

jsStartedAt :: Lens' JobSummary (Maybe Integer) Source #

The Unix time stamp for when the job was started (when the job transitioned from the STARTING state to the RUNNING state).

jsContainer :: Lens' JobSummary (Maybe ContainerSummary) Source #

An object representing the details of the container that is associated with the job.

jsStatusReason :: Lens' JobSummary (Maybe Text) Source #

A short, human-readable string to provide additional details about the current status of the job.

jsArrayProperties :: Lens' JobSummary (Maybe ArrayPropertiesSummary) Source #

The array properties of the job, if it is an array job.

jsJobId :: Lens' JobSummary Text Source #

The ID of the job.

jsJobName :: Lens' JobSummary Text Source #

The name of the job.

JobTimeout

data JobTimeout Source #

An object representing a job timeout configuration.

See: jobTimeout smart constructor.

Instances
Eq JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: JobTimeout -> Constr #

dataTypeOf :: JobTimeout -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep JobTimeout :: Type -> Type #

Hashable JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: JobTimeout -> () #

type Rep JobTimeout Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep JobTimeout = D1 (MetaData "JobTimeout" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" True) (C1 (MetaCons "JobTimeout'" PrefixI True) (S1 (MetaSel (Just "_jtAttemptDurationSeconds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))

jobTimeout :: JobTimeout Source #

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

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

  • jtAttemptDurationSeconds - The time duration in seconds (measured from the job attempt's startedAt timestamp) after which AWS Batch terminates your jobs if they have not finished.

jtAttemptDurationSeconds :: Lens' JobTimeout (Maybe Int) Source #

The time duration in seconds (measured from the job attempt's startedAt timestamp) after which AWS Batch terminates your jobs if they have not finished.

KeyValuePair

data KeyValuePair Source #

A key-value pair object.

See: keyValuePair smart constructor.

Instances
Eq KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: KeyValuePair -> Constr #

dataTypeOf :: KeyValuePair -> DataType #

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

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

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

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

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

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

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

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

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

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

Read KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep KeyValuePair :: Type -> Type #

Hashable KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: KeyValuePair -> () #

type Rep KeyValuePair Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep KeyValuePair = D1 (MetaData "KeyValuePair" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "KeyValuePair'" PrefixI True) (S1 (MetaSel (Just "_kvpValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_kvpName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

keyValuePair :: KeyValuePair Source #

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

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

  • kvpValue - The value of the key-value pair. For environment variables, this is the value of the environment variable.
  • kvpName - The name of the key-value pair. For environment variables, this is the name of the environment variable.

kvpValue :: Lens' KeyValuePair (Maybe Text) Source #

The value of the key-value pair. For environment variables, this is the value of the environment variable.

kvpName :: Lens' KeyValuePair (Maybe Text) Source #

The name of the key-value pair. For environment variables, this is the name of the environment variable.

MountPoint

data MountPoint Source #

Details on a Docker volume mount point that is used in a job's container properties.

See: mountPoint smart constructor.

Instances
Eq MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: MountPoint -> Constr #

dataTypeOf :: MountPoint -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep MountPoint :: Type -> Type #

Hashable MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: MountPoint -> () #

type Rep MountPoint Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep MountPoint = D1 (MetaData "MountPoint" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "MountPoint'" PrefixI True) (S1 (MetaSel (Just "_mpContainerPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_mpSourceVolume") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_mpReadOnly") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

mountPoint :: MountPoint Source #

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

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

  • mpContainerPath - The path on the container at which to mount the host volume.
  • mpSourceVolume - The name of the volume to mount.
  • mpReadOnly - If this value is true , the container has read-only access to the volume; otherwise, the container can write to the volume. The default value is false .

mpContainerPath :: Lens' MountPoint (Maybe Text) Source #

The path on the container at which to mount the host volume.

mpSourceVolume :: Lens' MountPoint (Maybe Text) Source #

The name of the volume to mount.

mpReadOnly :: Lens' MountPoint (Maybe Bool) Source #

If this value is true , the container has read-only access to the volume; otherwise, the container can write to the volume. The default value is false .

RetryStrategy

data RetryStrategy Source #

The retry strategy associated with a job.

See: retryStrategy smart constructor.

Instances
Eq RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Data RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: RetryStrategy -> Constr #

dataTypeOf :: RetryStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep RetryStrategy :: Type -> Type #

Hashable RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

ToJSON RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: RetryStrategy -> () #

type Rep RetryStrategy Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep RetryStrategy = D1 (MetaData "RetryStrategy" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" True) (C1 (MetaCons "RetryStrategy'" PrefixI True) (S1 (MetaSel (Just "_rsAttempts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))

retryStrategy :: RetryStrategy Source #

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

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

  • rsAttempts - The number of times to move a job to the RUNNABLE status. You may specify between 1 and 10 attempts. If the value of attempts is greater than one, the job is retried if it fails until it has moved to RUNNABLE that many times.

rsAttempts :: Lens' RetryStrategy (Maybe Int) Source #

The number of times to move a job to the RUNNABLE status. You may specify between 1 and 10 attempts. If the value of attempts is greater than one, the job is retried if it fails until it has moved to RUNNABLE that many times.

Ulimit

data Ulimit Source #

The ulimit settings to pass to the container.

See: ulimit smart constructor.

Instances
Eq Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

Data Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: Ulimit -> Constr #

dataTypeOf :: Ulimit -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep Ulimit :: Type -> Type #

Methods

from :: Ulimit -> Rep Ulimit x #

to :: Rep Ulimit x -> Ulimit #

Hashable Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

hashWithSalt :: Int -> Ulimit -> Int #

hash :: Ulimit -> Int #

ToJSON Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: Ulimit -> () #

type Rep Ulimit Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep Ulimit = D1 (MetaData "Ulimit" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "Ulimit'" PrefixI True) (S1 (MetaSel (Just "_uHardLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "_uName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_uSoftLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

ulimit Source #

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

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

  • uHardLimit - The hard limit for the ulimit type.
  • uName - The type of the ulimit .
  • uSoftLimit - The soft limit for the ulimit type.

uHardLimit :: Lens' Ulimit Int Source #

The hard limit for the ulimit type.

uName :: Lens' Ulimit Text Source #

The type of the ulimit .

uSoftLimit :: Lens' Ulimit Int Source #

The soft limit for the ulimit type.

Volume

data Volume Source #

A data volume used in a job's container properties.

See: volume smart constructor.

Instances
Eq Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

Data Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

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

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

toConstr :: Volume -> Constr #

dataTypeOf :: Volume -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Show Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Generic Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Associated Types

type Rep Volume :: Type -> Type #

Methods

from :: Volume -> Rep Volume x #

to :: Rep Volume x -> Volume #

Hashable Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

hashWithSalt :: Int -> Volume -> Int #

hash :: Volume -> Int #

ToJSON Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

FromJSON Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

NFData Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

Methods

rnf :: Volume -> () #

type Rep Volume Source # 
Instance details

Defined in Network.AWS.Batch.Types.Product

type Rep Volume = D1 (MetaData "Volume" "Network.AWS.Batch.Types.Product" "amazonka-batch-1.6.1-Ehms0ZM7bO3CGJpCkHVC0C" False) (C1 (MetaCons "Volume'" PrefixI True) (S1 (MetaSel (Just "_vName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_vHost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Host))))

volume :: Volume Source #

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

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

  • vName - The name of the volume. Up to 255 letters (uppercase and lowercase), numbers, hyphens, and underscores are allowed. This name is referenced in the sourceVolume parameter of container definition mountPoints .
  • vHost - The contents of the host parameter determine whether your data volume persists on the host container instance and where it is stored. If the host parameter is empty, then the Docker daemon assigns a host path for your data volume. However, the data is not guaranteed to persist after the containers associated with it stop running.

vName :: Lens' Volume (Maybe Text) Source #

The name of the volume. Up to 255 letters (uppercase and lowercase), numbers, hyphens, and underscores are allowed. This name is referenced in the sourceVolume parameter of container definition mountPoints .

vHost :: Lens' Volume (Maybe Host) Source #

The contents of the host parameter determine whether your data volume persists on the host container instance and where it is stored. If the host parameter is empty, then the Docker daemon assigns a host path for your data volume. However, the data is not guaranteed to persist after the containers associated with it stop running.