amazonka-glue-1.6.0: Amazon Glue 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.Glue.Types

Contents

Description

 

Synopsis

Service Configuration

glue :: Service Source #

API version 2017-03-31 of the Amazon Glue SDK configuration.

Errors

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

A value could not be validated.

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

Access to a resource was denied.

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

The operation cannot be performed because the crawler is already running.

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

The specified scheduler is transitioning.

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

The specified scheduler is already running.

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

Too many jobs are being run concurrently.

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

There is no applicable schedule.

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

The specified crawler is not running.

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

A specified entity does not exist

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

Two processes are trying to modify a resource simultaneously.

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

The specified scheduler is not running.

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

An internal service error occurred.

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

The input provided was not valid.

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

A resource numerical limit was exceeded.

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

The same unique identifier was associated with two different records.

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

The specified crawler is stopping.

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

A resource to be created or added already exists.

ConnectionPropertyKey

data ConnectionPropertyKey Source #

Instances

Bounded ConnectionPropertyKey Source # 
Enum ConnectionPropertyKey Source # 
Eq ConnectionPropertyKey Source # 
Data ConnectionPropertyKey Source # 

Methods

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

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

toConstr :: ConnectionPropertyKey -> Constr #

dataTypeOf :: ConnectionPropertyKey -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ConnectionPropertyKey -> () #

ToHeader ConnectionPropertyKey Source # 
ToQuery ConnectionPropertyKey Source # 
ToByteString ConnectionPropertyKey Source # 
FromText ConnectionPropertyKey Source # 
ToText ConnectionPropertyKey Source # 
type Rep ConnectionPropertyKey Source # 
type Rep ConnectionPropertyKey = D1 * (MetaData "ConnectionPropertyKey" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ConfigFiles" PrefixI False) (U1 *)) (C1 * (MetaCons "Host" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "InstanceId" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "JdbcConnectionURL" PrefixI False) (U1 *)) (C1 * (MetaCons "JdbcDriverClassName" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "JdbcDriverJARURI" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "JdbcEngine" PrefixI False) (U1 *)) (C1 * (MetaCons "JdbcEngineVersion" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Password" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Port" PrefixI False) (U1 *)) (C1 * (MetaCons "Username" PrefixI False) (U1 *))))))

ConnectionType

data ConnectionType Source #

Constructors

Jdbc 
Sftp 

Instances

Bounded ConnectionType Source # 
Enum ConnectionType Source # 
Eq ConnectionType Source # 
Data ConnectionType Source # 

Methods

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

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

toConstr :: ConnectionType -> Constr #

dataTypeOf :: ConnectionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ConnectionType Source # 
Read ConnectionType Source # 
Show ConnectionType Source # 
Generic ConnectionType Source # 

Associated Types

type Rep ConnectionType :: * -> * #

Hashable ConnectionType Source # 
ToJSON ConnectionType Source # 
FromJSON ConnectionType Source # 
NFData ConnectionType Source # 

Methods

rnf :: ConnectionType -> () #

ToHeader ConnectionType Source # 
ToQuery ConnectionType Source # 
ToByteString ConnectionType Source # 
FromText ConnectionType Source # 
ToText ConnectionType Source # 
type Rep ConnectionType Source # 
type Rep ConnectionType = D1 * (MetaData "ConnectionType" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "Jdbc" PrefixI False) (U1 *)) (C1 * (MetaCons "Sftp" PrefixI False) (U1 *)))

CrawlerState

data CrawlerState Source #

Constructors

CSReady 
CSRunning 
CSStopping 

Instances

Bounded CrawlerState Source # 
Enum CrawlerState Source # 
Eq CrawlerState Source # 
Data CrawlerState Source # 

Methods

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

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

toConstr :: CrawlerState -> Constr #

dataTypeOf :: CrawlerState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CrawlerState Source # 
Read CrawlerState Source # 
Show CrawlerState Source # 
Generic CrawlerState Source # 

Associated Types

type Rep CrawlerState :: * -> * #

Hashable CrawlerState Source # 
FromJSON CrawlerState Source # 
NFData CrawlerState Source # 

Methods

rnf :: CrawlerState -> () #

ToHeader CrawlerState Source # 
ToQuery CrawlerState Source # 
ToByteString CrawlerState Source # 
FromText CrawlerState Source # 
ToText CrawlerState Source # 

Methods

toText :: CrawlerState -> Text #

type Rep CrawlerState Source # 
type Rep CrawlerState = D1 * (MetaData "CrawlerState" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "CSReady" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CSRunning" PrefixI False) (U1 *)) (C1 * (MetaCons "CSStopping" PrefixI False) (U1 *))))

DeleteBehavior

data DeleteBehavior Source #

Instances

Bounded DeleteBehavior Source # 
Enum DeleteBehavior Source # 
Eq DeleteBehavior Source # 
Data DeleteBehavior Source # 

Methods

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

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

toConstr :: DeleteBehavior -> Constr #

dataTypeOf :: DeleteBehavior -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DeleteBehavior Source # 
Read DeleteBehavior Source # 
Show DeleteBehavior Source # 
Generic DeleteBehavior Source # 

Associated Types

type Rep DeleteBehavior :: * -> * #

Hashable DeleteBehavior Source # 
ToJSON DeleteBehavior Source # 
FromJSON DeleteBehavior Source # 
NFData DeleteBehavior Source # 

Methods

rnf :: DeleteBehavior -> () #

ToHeader DeleteBehavior Source # 
ToQuery DeleteBehavior Source # 
ToByteString DeleteBehavior Source # 
FromText DeleteBehavior Source # 
ToText DeleteBehavior Source # 
type Rep DeleteBehavior Source # 
type Rep DeleteBehavior = D1 * (MetaData "DeleteBehavior" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "DeleteFromDatabase" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DeprecateInDatabase" PrefixI False) (U1 *)) (C1 * (MetaCons "Log" PrefixI False) (U1 *))))

JobRunState

data JobRunState Source #

Instances

Bounded JobRunState Source # 
Enum JobRunState Source # 
Eq JobRunState Source # 
Data JobRunState Source # 

Methods

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

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

toConstr :: JobRunState -> Constr #

dataTypeOf :: JobRunState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JobRunState Source # 
Read JobRunState Source # 
Show JobRunState Source # 
Generic JobRunState Source # 

Associated Types

type Rep JobRunState :: * -> * #

Hashable JobRunState Source # 
ToJSON JobRunState Source # 
FromJSON JobRunState Source # 
NFData JobRunState Source # 

Methods

rnf :: JobRunState -> () #

ToHeader JobRunState Source # 
ToQuery JobRunState Source # 
ToByteString JobRunState Source # 
FromText JobRunState Source # 
ToText JobRunState Source # 

Methods

toText :: JobRunState -> Text #

type Rep JobRunState Source # 
type Rep JobRunState = D1 * (MetaData "JobRunState" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Failed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Running" PrefixI False) (U1 *)) (C1 * (MetaCons "Starting" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Stopped" PrefixI False) (U1 *)) (C1 * (MetaCons "Stopping" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Succeeded" PrefixI False) (U1 *)) (C1 * (MetaCons "Timeout" PrefixI False) (U1 *)))))

Language

data Language Source #

Constructors

Python 
Scala 

Instances

Bounded Language Source # 
Enum Language Source # 
Eq Language Source # 
Data Language Source # 

Methods

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

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

toConstr :: Language -> Constr #

dataTypeOf :: Language -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Language Source # 
Read Language Source # 
Show Language Source # 
Generic Language Source # 

Associated Types

type Rep Language :: * -> * #

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

Hashable Language Source # 

Methods

hashWithSalt :: Int -> Language -> Int #

hash :: Language -> Int #

ToJSON Language Source # 
NFData Language Source # 

Methods

rnf :: Language -> () #

ToHeader Language Source # 

Methods

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

ToQuery Language Source # 
ToByteString Language Source # 

Methods

toBS :: Language -> ByteString #

FromText Language Source # 
ToText Language Source # 

Methods

toText :: Language -> Text #

type Rep Language Source # 
type Rep Language = D1 * (MetaData "Language" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "Python" PrefixI False) (U1 *)) (C1 * (MetaCons "Scala" PrefixI False) (U1 *)))

LastCrawlStatus

data LastCrawlStatus Source #

Instances

Bounded LastCrawlStatus Source # 
Enum LastCrawlStatus Source # 
Eq LastCrawlStatus Source # 
Data LastCrawlStatus Source # 

Methods

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

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

toConstr :: LastCrawlStatus -> Constr #

dataTypeOf :: LastCrawlStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: LastCrawlStatus -> () #

ToHeader LastCrawlStatus Source # 
ToQuery LastCrawlStatus Source # 
ToByteString LastCrawlStatus Source # 
FromText LastCrawlStatus Source # 
ToText LastCrawlStatus Source # 
type Rep LastCrawlStatus Source # 
type Rep LastCrawlStatus = D1 * (MetaData "LastCrawlStatus" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "LCSCancelled" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LCSFailed" PrefixI False) (U1 *)) (C1 * (MetaCons "LCSSucceeded" PrefixI False) (U1 *))))

Logical

data Logical Source #

Constructors

And 
Any 

Instances

Bounded Logical Source # 
Enum Logical Source # 
Eq Logical Source # 

Methods

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

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

Data Logical Source # 

Methods

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

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

toConstr :: Logical -> Constr #

dataTypeOf :: Logical -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Logical Source # 
Read Logical Source # 
Show Logical Source # 
Generic Logical Source # 

Associated Types

type Rep Logical :: * -> * #

Methods

from :: Logical -> Rep Logical x #

to :: Rep Logical x -> Logical #

Hashable Logical Source # 

Methods

hashWithSalt :: Int -> Logical -> Int #

hash :: Logical -> Int #

ToJSON Logical Source # 
FromJSON Logical Source # 
NFData Logical Source # 

Methods

rnf :: Logical -> () #

ToHeader Logical Source # 

Methods

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

ToQuery Logical Source # 
ToByteString Logical Source # 

Methods

toBS :: Logical -> ByteString #

FromText Logical Source # 
ToText Logical Source # 

Methods

toText :: Logical -> Text #

type Rep Logical Source # 
type Rep Logical = D1 * (MetaData "Logical" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "And" PrefixI False) (U1 *)) (C1 * (MetaCons "Any" PrefixI False) (U1 *)))

LogicalOperator

data LogicalOperator Source #

Constructors

Equals 

Instances

Bounded LogicalOperator Source # 
Enum LogicalOperator Source # 
Eq LogicalOperator Source # 
Data LogicalOperator Source # 

Methods

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

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

toConstr :: LogicalOperator -> Constr #

dataTypeOf :: LogicalOperator -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: LogicalOperator -> () #

ToHeader LogicalOperator Source # 
ToQuery LogicalOperator Source # 
ToByteString LogicalOperator Source # 
FromText LogicalOperator Source # 
ToText LogicalOperator Source # 
type Rep LogicalOperator Source # 
type Rep LogicalOperator = D1 * (MetaData "LogicalOperator" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Equals" PrefixI False) (U1 *))

PrincipalType

data PrincipalType Source #

Constructors

Group 
Role 
User 

Instances

Bounded PrincipalType Source # 
Enum PrincipalType Source # 
Eq PrincipalType Source # 
Data PrincipalType Source # 

Methods

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

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

toConstr :: PrincipalType -> Constr #

dataTypeOf :: PrincipalType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PrincipalType Source # 
Read PrincipalType Source # 
Show PrincipalType Source # 
Generic PrincipalType Source # 

Associated Types

type Rep PrincipalType :: * -> * #

Hashable PrincipalType Source # 
ToJSON PrincipalType Source # 
FromJSON PrincipalType Source # 
NFData PrincipalType Source # 

Methods

rnf :: PrincipalType -> () #

ToHeader PrincipalType Source # 
ToQuery PrincipalType Source # 
ToByteString PrincipalType Source # 
FromText PrincipalType Source # 
ToText PrincipalType Source # 

Methods

toText :: PrincipalType -> Text #

type Rep PrincipalType Source # 
type Rep PrincipalType = D1 * (MetaData "PrincipalType" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "Group" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Role" PrefixI False) (U1 *)) (C1 * (MetaCons "User" PrefixI False) (U1 *))))

ResourceType

data ResourceType Source #

Constructors

Archive 
File 
JAR 

Instances

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

Methods

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

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

toConstr :: ResourceType -> Constr #

dataTypeOf :: ResourceType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep ResourceType :: * -> * #

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

Methods

rnf :: ResourceType -> () #

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

Methods

toText :: ResourceType -> Text #

type Rep ResourceType Source # 
type Rep ResourceType = D1 * (MetaData "ResourceType" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "Archive" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "File" PrefixI False) (U1 *)) (C1 * (MetaCons "JAR" PrefixI False) (U1 *))))

ScheduleState

data ScheduleState Source #

Instances

Bounded ScheduleState Source # 
Enum ScheduleState Source # 
Eq ScheduleState Source # 
Data ScheduleState Source # 

Methods

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

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

toConstr :: ScheduleState -> Constr #

dataTypeOf :: ScheduleState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ScheduleState Source # 
Read ScheduleState Source # 
Show ScheduleState Source # 
Generic ScheduleState Source # 

Associated Types

type Rep ScheduleState :: * -> * #

Hashable ScheduleState Source # 
FromJSON ScheduleState Source # 
NFData ScheduleState Source # 

Methods

rnf :: ScheduleState -> () #

ToHeader ScheduleState Source # 
ToQuery ScheduleState Source # 
ToByteString ScheduleState Source # 
FromText ScheduleState Source # 
ToText ScheduleState Source # 

Methods

toText :: ScheduleState -> Text #

type Rep ScheduleState Source # 
type Rep ScheduleState = D1 * (MetaData "ScheduleState" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "NotScheduled" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Scheduled" PrefixI False) (U1 *)) (C1 * (MetaCons "Transitioning" PrefixI False) (U1 *))))

TriggerState

data TriggerState Source #

Instances

Bounded TriggerState Source # 
Enum TriggerState Source # 
Eq TriggerState Source # 
Data TriggerState Source # 

Methods

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

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

toConstr :: TriggerState -> Constr #

dataTypeOf :: TriggerState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TriggerState Source # 
Read TriggerState Source # 
Show TriggerState Source # 
Generic TriggerState Source # 

Associated Types

type Rep TriggerState :: * -> * #

Hashable TriggerState Source # 
FromJSON TriggerState Source # 
NFData TriggerState Source # 

Methods

rnf :: TriggerState -> () #

ToHeader TriggerState Source # 
ToQuery TriggerState Source # 
ToByteString TriggerState Source # 
FromText TriggerState Source # 
ToText TriggerState Source # 

Methods

toText :: TriggerState -> Text #

type Rep TriggerState Source # 
type Rep TriggerState = D1 * (MetaData "TriggerState" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Activated" PrefixI False) (U1 *)) (C1 * (MetaCons "Activating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Created" PrefixI False) (U1 *)) (C1 * (MetaCons "Creating" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Deactivated" PrefixI False) (U1 *)) (C1 * (MetaCons "Deactivating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Deleting" PrefixI False) (U1 *)) (C1 * (MetaCons "Updating" PrefixI False) (U1 *)))))

TriggerType

data TriggerType Source #

Instances

Bounded TriggerType Source # 
Enum TriggerType Source # 
Eq TriggerType Source # 
Data TriggerType Source # 

Methods

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

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

toConstr :: TriggerType -> Constr #

dataTypeOf :: TriggerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TriggerType Source # 
Read TriggerType Source # 
Show TriggerType Source # 
Generic TriggerType Source # 

Associated Types

type Rep TriggerType :: * -> * #

Hashable TriggerType Source # 
ToJSON TriggerType Source # 
FromJSON TriggerType Source # 
NFData TriggerType Source # 

Methods

rnf :: TriggerType -> () #

ToHeader TriggerType Source # 
ToQuery TriggerType Source # 
ToByteString TriggerType Source # 
FromText TriggerType Source # 
ToText TriggerType Source # 

Methods

toText :: TriggerType -> Text #

type Rep TriggerType Source # 
type Rep TriggerType = D1 * (MetaData "TriggerType" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "TTConditional" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TTOnDemand" PrefixI False) (U1 *)) (C1 * (MetaCons "TTScheduled" PrefixI False) (U1 *))))

UpdateBehavior

data UpdateBehavior Source #

Constructors

UBLog 
UBUpdateInDatabase 

Instances

Bounded UpdateBehavior Source # 
Enum UpdateBehavior Source # 
Eq UpdateBehavior Source # 
Data UpdateBehavior Source # 

Methods

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

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

toConstr :: UpdateBehavior -> Constr #

dataTypeOf :: UpdateBehavior -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UpdateBehavior Source # 
Read UpdateBehavior Source # 
Show UpdateBehavior Source # 
Generic UpdateBehavior Source # 

Associated Types

type Rep UpdateBehavior :: * -> * #

Hashable UpdateBehavior Source # 
ToJSON UpdateBehavior Source # 
FromJSON UpdateBehavior Source # 
NFData UpdateBehavior Source # 

Methods

rnf :: UpdateBehavior -> () #

ToHeader UpdateBehavior Source # 
ToQuery UpdateBehavior Source # 
ToByteString UpdateBehavior Source # 
FromText UpdateBehavior Source # 
ToText UpdateBehavior Source # 
type Rep UpdateBehavior Source # 
type Rep UpdateBehavior = D1 * (MetaData "UpdateBehavior" "Network.AWS.Glue.Types.Sum" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) ((:+:) * (C1 * (MetaCons "UBLog" PrefixI False) (U1 *)) (C1 * (MetaCons "UBUpdateInDatabase" PrefixI False) (U1 *)))

Action

data Action Source #

Defines an action to be initiated by a trigger.

See: action smart constructor.

Instances

Eq Action Source # 

Methods

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

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

Data Action Source # 

Methods

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

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

toConstr :: Action -> Constr #

dataTypeOf :: Action -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Action Source # 
Show Action Source # 
Generic Action Source # 

Associated Types

type Rep Action :: * -> * #

Methods

from :: Action -> Rep Action x #

to :: Rep Action x -> Action #

Hashable Action Source # 

Methods

hashWithSalt :: Int -> Action -> Int #

hash :: Action -> Int #

ToJSON Action Source # 
FromJSON Action Source # 
NFData Action Source # 

Methods

rnf :: Action -> () #

type Rep Action Source # 
type Rep Action = D1 * (MetaData "Action" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Action'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_aArguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_aTimeout") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))))))

action :: Action Source #

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

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

  • aArguments - Arguments to be passed to the job. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own Job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.
  • aJobName - The name of a job to be executed.
  • aTimeout - The job run timeout in minutes. It overrides the timeout value of the job.

aArguments :: Lens' Action (HashMap Text Text) Source #

Arguments to be passed to the job. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own Job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.

aJobName :: Lens' Action (Maybe Text) Source #

The name of a job to be executed.

aTimeout :: Lens' Action (Maybe Natural) Source #

The job run timeout in minutes. It overrides the timeout value of the job.

BatchStopJobRunError

data BatchStopJobRunError Source #

Records an error that occurred when attempting to stop a specified job run.

See: batchStopJobRunError smart constructor.

Instances

Eq BatchStopJobRunError Source # 
Data BatchStopJobRunError Source # 

Methods

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

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

toConstr :: BatchStopJobRunError -> Constr #

dataTypeOf :: BatchStopJobRunError -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: BatchStopJobRunError -> () #

type Rep BatchStopJobRunError Source # 
type Rep BatchStopJobRunError = D1 * (MetaData "BatchStopJobRunError" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "BatchStopJobRunError'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bsjreJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bsjreJobRunId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_bsjreErrorDetail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ErrorDetail))))))

batchStopJobRunError :: BatchStopJobRunError Source #

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

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

  • bsjreJobName - The name of the job definition used in the job run in question.
  • bsjreJobRunId - The JobRunId of the job run in question.
  • bsjreErrorDetail - Specifies details about the error that was encountered.

bsjreJobName :: Lens' BatchStopJobRunError (Maybe Text) Source #

The name of the job definition used in the job run in question.

bsjreJobRunId :: Lens' BatchStopJobRunError (Maybe Text) Source #

The JobRunId of the job run in question.

bsjreErrorDetail :: Lens' BatchStopJobRunError (Maybe ErrorDetail) Source #

Specifies details about the error that was encountered.

BatchStopJobRunSuccessfulSubmission

data BatchStopJobRunSuccessfulSubmission Source #

Records a successful request to stop a specified JobRun.

See: batchStopJobRunSuccessfulSubmission smart constructor.

Instances

Eq BatchStopJobRunSuccessfulSubmission Source # 
Data BatchStopJobRunSuccessfulSubmission Source # 

Methods

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

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

toConstr :: BatchStopJobRunSuccessfulSubmission -> Constr #

dataTypeOf :: BatchStopJobRunSuccessfulSubmission -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BatchStopJobRunSuccessfulSubmission Source # 
Show BatchStopJobRunSuccessfulSubmission Source # 
Generic BatchStopJobRunSuccessfulSubmission Source # 
Hashable BatchStopJobRunSuccessfulSubmission Source # 
FromJSON BatchStopJobRunSuccessfulSubmission Source # 
NFData BatchStopJobRunSuccessfulSubmission Source # 
type Rep BatchStopJobRunSuccessfulSubmission Source # 
type Rep BatchStopJobRunSuccessfulSubmission = D1 * (MetaData "BatchStopJobRunSuccessfulSubmission" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "BatchStopJobRunSuccessfulSubmission'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bsjrssJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_bsjrssJobRunId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

batchStopJobRunSuccessfulSubmission :: BatchStopJobRunSuccessfulSubmission Source #

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

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

  • bsjrssJobName - The name of the job definition used in the job run that was stopped.
  • bsjrssJobRunId - The JobRunId of the job run that was stopped.

bsjrssJobName :: Lens' BatchStopJobRunSuccessfulSubmission (Maybe Text) Source #

The name of the job definition used in the job run that was stopped.

bsjrssJobRunId :: Lens' BatchStopJobRunSuccessfulSubmission (Maybe Text) Source #

The JobRunId of the job run that was stopped.

CatalogEntry

data CatalogEntry Source #

Specifies a table definition in the Data Catalog.

See: catalogEntry smart constructor.

Instances

Eq CatalogEntry Source # 
Data CatalogEntry Source # 

Methods

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

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

toConstr :: CatalogEntry -> Constr #

dataTypeOf :: CatalogEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CatalogEntry Source # 
Show CatalogEntry Source # 
Generic CatalogEntry Source # 

Associated Types

type Rep CatalogEntry :: * -> * #

Hashable CatalogEntry Source # 
ToJSON CatalogEntry Source # 
NFData CatalogEntry Source # 

Methods

rnf :: CatalogEntry -> () #

type Rep CatalogEntry Source # 
type Rep CatalogEntry = D1 * (MetaData "CatalogEntry" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CatalogEntry'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ceDatabaseName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_ceTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

catalogEntry Source #

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

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

ceDatabaseName :: Lens' CatalogEntry Text Source #

The database in which the table metadata resides.

ceTableName :: Lens' CatalogEntry Text Source #

The name of the table in question.

CatalogImportStatus

data CatalogImportStatus Source #

A structure containing migration status information.

See: catalogImportStatus smart constructor.

Instances

Eq CatalogImportStatus Source # 
Data CatalogImportStatus Source # 

Methods

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

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

toConstr :: CatalogImportStatus -> Constr #

dataTypeOf :: CatalogImportStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: CatalogImportStatus -> () #

type Rep CatalogImportStatus Source # 
type Rep CatalogImportStatus = D1 * (MetaData "CatalogImportStatus" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CatalogImportStatus'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cisImportedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cisImportTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_cisImportCompleted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))))

catalogImportStatus :: CatalogImportStatus Source #

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

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

cisImportedBy :: Lens' CatalogImportStatus (Maybe Text) Source #

The name of the person who initiated the migration.

cisImportTime :: Lens' CatalogImportStatus (Maybe UTCTime) Source #

The time that the migration was started.

cisImportCompleted :: Lens' CatalogImportStatus (Maybe Bool) Source #

True if the migration has completed, or False otherwise.

Classifier

data Classifier Source #

Classifiers are written in Python and triggered during a crawl task. You can write your own classifiers to best categorize your data sources and specify the appropriate schemas to use for them. A classifier checks whether a given file is in a format it can handle, and if it is, the classifier creates a schema in the form of a StructType object that matches that data format.

A classifier can be a grok classifier, an XML classifier, or a JSON classifier, asspecified in one of the fields in the Classifier object.

See: classifier smart constructor.

Instances

Eq Classifier Source # 
Data Classifier Source # 

Methods

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

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

toConstr :: Classifier -> Constr #

dataTypeOf :: Classifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Classifier Source # 
Show Classifier Source # 
Generic Classifier Source # 

Associated Types

type Rep Classifier :: * -> * #

Hashable Classifier Source # 
FromJSON Classifier Source # 
NFData Classifier Source # 

Methods

rnf :: Classifier -> () #

type Rep Classifier Source # 
type Rep Classifier = D1 * (MetaData "Classifier" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Classifier'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cGrokClassifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe GrokClassifier))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cXMLClassifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe XMLClassifier))) (S1 * (MetaSel (Just Symbol "_cJSONClassifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe JSONClassifier))))))

classifier :: Classifier Source #

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

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

CodeGenEdge

data CodeGenEdge Source #

Represents a directional edge in a directed acyclic graph (DAG).

See: codeGenEdge smart constructor.

Instances

Eq CodeGenEdge Source # 
Data CodeGenEdge Source # 

Methods

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

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

toConstr :: CodeGenEdge -> Constr #

dataTypeOf :: CodeGenEdge -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CodeGenEdge Source # 
Show CodeGenEdge Source # 
Generic CodeGenEdge Source # 

Associated Types

type Rep CodeGenEdge :: * -> * #

Hashable CodeGenEdge Source # 
ToJSON CodeGenEdge Source # 
FromJSON CodeGenEdge Source # 
NFData CodeGenEdge Source # 

Methods

rnf :: CodeGenEdge -> () #

type Rep CodeGenEdge Source # 
type Rep CodeGenEdge = D1 * (MetaData "CodeGenEdge" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CodeGenEdge'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cgeTargetParameter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cgeSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cgeTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

codeGenEdge Source #

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

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

cgeTargetParameter :: Lens' CodeGenEdge (Maybe Text) Source #

The target of the edge.

cgeSource :: Lens' CodeGenEdge Text Source #

The ID of the node at which the edge starts.

cgeTarget :: Lens' CodeGenEdge Text Source #

The ID of the node at which the edge ends.

CodeGenNode

data CodeGenNode Source #

Represents a node in a directed acyclic graph (DAG)

See: codeGenNode smart constructor.

Instances

Eq CodeGenNode Source # 
Data CodeGenNode Source # 

Methods

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

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

toConstr :: CodeGenNode -> Constr #

dataTypeOf :: CodeGenNode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CodeGenNode Source # 
Show CodeGenNode Source # 
Generic CodeGenNode Source # 

Associated Types

type Rep CodeGenNode :: * -> * #

Hashable CodeGenNode Source # 
ToJSON CodeGenNode Source # 
FromJSON CodeGenNode Source # 
NFData CodeGenNode Source # 

Methods

rnf :: CodeGenNode -> () #

type Rep CodeGenNode Source # 
type Rep CodeGenNode = D1 * (MetaData "CodeGenNode" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CodeGenNode'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cgnLineNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_cgnId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cgnNodeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cgnArgs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [CodeGenNodeArg])))))

codeGenNode Source #

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

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

  • cgnLineNumber - The line number of the node.
  • cgnId - A node identifier that is unique within the node's graph.
  • cgnNodeType - The type of node this is.
  • cgnArgs - Properties of the node, in the form of name-value pairs.

cgnLineNumber :: Lens' CodeGenNode (Maybe Int) Source #

The line number of the node.

cgnId :: Lens' CodeGenNode Text Source #

A node identifier that is unique within the node's graph.

cgnNodeType :: Lens' CodeGenNode Text Source #

The type of node this is.

cgnArgs :: Lens' CodeGenNode [CodeGenNodeArg] Source #

Properties of the node, in the form of name-value pairs.

CodeGenNodeArg

data CodeGenNodeArg Source #

An argument or property of a node.

See: codeGenNodeArg smart constructor.

Instances

Eq CodeGenNodeArg Source # 
Data CodeGenNodeArg Source # 

Methods

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

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

toConstr :: CodeGenNodeArg -> Constr #

dataTypeOf :: CodeGenNodeArg -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CodeGenNodeArg Source # 
Show CodeGenNodeArg Source # 
Generic CodeGenNodeArg Source # 

Associated Types

type Rep CodeGenNodeArg :: * -> * #

Hashable CodeGenNodeArg Source # 
ToJSON CodeGenNodeArg Source # 
FromJSON CodeGenNodeArg Source # 
NFData CodeGenNodeArg Source # 

Methods

rnf :: CodeGenNodeArg -> () #

type Rep CodeGenNodeArg Source # 
type Rep CodeGenNodeArg = D1 * (MetaData "CodeGenNodeArg" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CodeGenNodeArg'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cgnaParam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cgnaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cgnaValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

codeGenNodeArg Source #

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

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

  • cgnaParam - True if the value is used as a parameter.
  • cgnaName - The name of the argument or property.
  • cgnaValue - The value of the argument or property.

cgnaParam :: Lens' CodeGenNodeArg (Maybe Bool) Source #

True if the value is used as a parameter.

cgnaName :: Lens' CodeGenNodeArg Text Source #

The name of the argument or property.

cgnaValue :: Lens' CodeGenNodeArg Text Source #

The value of the argument or property.

Column

data Column Source #

A column in a Table .

See: column smart constructor.

Instances

Eq Column Source # 

Methods

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

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

Data Column Source # 

Methods

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

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

toConstr :: Column -> Constr #

dataTypeOf :: Column -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Column Source # 
Show Column Source # 
Generic Column Source # 

Associated Types

type Rep Column :: * -> * #

Methods

from :: Column -> Rep Column x #

to :: Rep Column x -> Column #

Hashable Column Source # 

Methods

hashWithSalt :: Int -> Column -> Int #

hash :: Column -> Int #

ToJSON Column Source # 
FromJSON Column Source # 
NFData Column Source # 

Methods

rnf :: Column -> () #

type Rep Column Source # 
type Rep Column = D1 * (MetaData "Column" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Column'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

column Source #

Arguments

:: Text

cName

-> Column 

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

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

  • cType - The datatype of data in the Column .
  • cComment - Free-form text comment.
  • cName - The name of the Column .

cType :: Lens' Column (Maybe Text) Source #

The datatype of data in the Column .

cComment :: Lens' Column (Maybe Text) Source #

Free-form text comment.

cName :: Lens' Column Text Source #

The name of the Column .

Condition

data Condition Source #

Defines a condition under which a trigger fires.

See: condition smart constructor.

Instances

Eq Condition Source # 
Data Condition Source # 

Methods

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

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

toConstr :: Condition -> Constr #

dataTypeOf :: Condition -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Condition Source # 
Show Condition Source # 
Generic Condition Source # 

Associated Types

type Rep Condition :: * -> * #

Hashable Condition Source # 
ToJSON Condition Source # 
FromJSON Condition Source # 
NFData Condition Source # 

Methods

rnf :: Condition -> () #

type Rep Condition Source # 
type Rep Condition = D1 * (MetaData "Condition" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Condition'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe JobRunState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cLogicalOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LogicalOperator))))))

condition :: Condition Source #

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

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

  • cState - The condition state. Currently, the values supported are SUCCEEDED, STOPPED, TIMEOUT and FAILED.
  • cJobName - The name of the Job to whose JobRuns this condition applies and on which this trigger waits.
  • cLogicalOperator - A logical operator.

cState :: Lens' Condition (Maybe JobRunState) Source #

The condition state. Currently, the values supported are SUCCEEDED, STOPPED, TIMEOUT and FAILED.

cJobName :: Lens' Condition (Maybe Text) Source #

The name of the Job to whose JobRuns this condition applies and on which this trigger waits.

Connection

data Connection Source #

Defines a connection to a data source.

See: connection smart constructor.

Instances

Eq Connection Source # 
Data Connection Source # 

Methods

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

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

toConstr :: Connection -> Constr #

dataTypeOf :: Connection -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Connection Source # 
Show Connection Source # 
Generic Connection Source # 

Associated Types

type Rep Connection :: * -> * #

Hashable Connection Source # 
FromJSON Connection Source # 
NFData Connection Source # 

Methods

rnf :: Connection -> () #

type Rep Connection Source # 

connection :: Connection Source #

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

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

conCreationTime :: Lens' Connection (Maybe UTCTime) Source #

The time this connection definition was created.

conLastUpdatedBy :: Lens' Connection (Maybe Text) Source #

The user, group or role that last updated this connection definition.

conConnectionProperties :: Lens' Connection (HashMap ConnectionPropertyKey Text) Source #

A list of key-value pairs used as parameters for this connection.

conLastUpdatedTime :: Lens' Connection (Maybe UTCTime) Source #

The last time this connection definition was updated.

conMatchCriteria :: Lens' Connection [Text] Source #

A list of criteria that can be used in selecting this connection.

conPhysicalConnectionRequirements :: Lens' Connection (Maybe PhysicalConnectionRequirements) Source #

A map of physical connection requirements, such as VPC and SecurityGroup, needed for making this connection successfully.

conName :: Lens' Connection (Maybe Text) Source #

The name of the connection definition.

conDescription :: Lens' Connection (Maybe Text) Source #

Description of the connection.

conConnectionType :: Lens' Connection (Maybe ConnectionType) Source #

The type of the connection. Currently, only JDBC is supported; SFTP is not supported.

ConnectionInput

data ConnectionInput Source #

A structure used to specify a connection to create or update.

See: connectionInput smart constructor.

Instances

Eq ConnectionInput Source # 
Data ConnectionInput Source # 

Methods

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

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

toConstr :: ConnectionInput -> Constr #

dataTypeOf :: ConnectionInput -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ConnectionInput -> () #

type Rep ConnectionInput Source # 
type Rep ConnectionInput = D1 * (MetaData "ConnectionInput" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "ConnectionInput'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ciMatchCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciPhysicalConnectionRequirements") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PhysicalConnectionRequirements))) (S1 * (MetaSel (Just Symbol "_ciDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciConnectionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ConnectionType)) (S1 * (MetaSel (Just Symbol "_ciConnectionProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Map ConnectionPropertyKey Text)))))))

connectionInput Source #

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

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

ciMatchCriteria :: Lens' ConnectionInput [Text] Source #

A list of criteria that can be used in selecting this connection.

ciPhysicalConnectionRequirements :: Lens' ConnectionInput (Maybe PhysicalConnectionRequirements) Source #

A map of physical connection requirements, such as VPC and SecurityGroup, needed for making this connection successfully.

ciDescription :: Lens' ConnectionInput (Maybe Text) Source #

Description of the connection.

ciName :: Lens' ConnectionInput Text Source #

The name of the connection.

ciConnectionType :: Lens' ConnectionInput ConnectionType Source #

The type of the connection. Currently, only JDBC is supported; SFTP is not supported.

ciConnectionProperties :: Lens' ConnectionInput (HashMap ConnectionPropertyKey Text) Source #

A list of key-value pairs used as parameters for this connection.

ConnectionsList

data ConnectionsList Source #

Specifies the connections used by a job.

See: connectionsList smart constructor.

Instances

Eq ConnectionsList Source # 
Data ConnectionsList Source # 

Methods

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

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

toConstr :: ConnectionsList -> Constr #

dataTypeOf :: ConnectionsList -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ConnectionsList -> () #

type Rep ConnectionsList Source # 
type Rep ConnectionsList = D1 * (MetaData "ConnectionsList" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" True) (C1 * (MetaCons "ConnectionsList'" PrefixI True) (S1 * (MetaSel (Just Symbol "_clConnections") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Text]))))

connectionsList :: ConnectionsList Source #

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

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

clConnections :: Lens' ConnectionsList [Text] Source #

A list of connections used by the job.

Crawler

data Crawler Source #

Specifies a crawler program that examines a data source and uses classifiers to try to determine its schema. If successful, the crawler records metadata concerning the data source in the AWS Glue Data Catalog.

See: crawler smart constructor.

Instances

Eq Crawler Source # 

Methods

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

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

Data Crawler Source # 

Methods

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

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

toConstr :: Crawler -> Constr #

dataTypeOf :: Crawler -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Crawler Source # 
Show Crawler Source # 
Generic Crawler Source # 

Associated Types

type Rep Crawler :: * -> * #

Methods

from :: Crawler -> Rep Crawler x #

to :: Rep Crawler x -> Crawler #

Hashable Crawler Source # 

Methods

hashWithSalt :: Int -> Crawler -> Int #

hash :: Crawler -> Int #

FromJSON Crawler Source # 
NFData Crawler Source # 

Methods

rnf :: Crawler -> () #

type Rep Crawler Source # 
type Rep Crawler = D1 * (MetaData "Crawler" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Crawler'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_craCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_craState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe CrawlerState)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_craSchemaChangePolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SchemaChangePolicy))) (S1 * (MetaSel (Just Symbol "_craLastUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_craSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Schedule))) (S1 * (MetaSel (Just Symbol "_craLastCrawl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LastCrawlInfo)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_craCrawlElapsedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_craClassifiers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_craRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_craName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_craTargets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe CrawlerTargets))) (S1 * (MetaSel (Just Symbol "_craVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_craDatabaseName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_craConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_craTablePrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_craDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

crawler :: Crawler Source #

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

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

  • craCreationTime - The time when the crawler was created.
  • craState - Indicates whether the crawler is running, or whether a run is pending.
  • craSchemaChangePolicy - Sets the behavior when the crawler finds a changed or deleted object.
  • craLastUpdated - The time the crawler was last updated.
  • craSchedule - For scheduled crawlers, the schedule when the crawler runs.
  • craLastCrawl - The status of the last crawl, and potentially error information if an error occurred.
  • craCrawlElapsedTime - If the crawler is running, contains the total time elapsed since the last crawl began.
  • craClassifiers - A list of custom classifiers associated with the crawler.
  • craRole - The IAM role (or ARN of an IAM role) used to access customer resources, such as data in Amazon S3.
  • craName - The crawler name.
  • craTargets - A collection of targets to crawl.
  • craVersion - The version of the crawler.
  • craDatabaseName - The database where metadata is written by this crawler.
  • craConfiguration - Crawler configuration information. This versioned JSON string allows users to specify aspects of a Crawler's behavior. You can use this field to force partitions to inherit metadata such as classification, input format, output format, serde information, and schema from their parent table, rather than detect this information separately for each partition. Use the following JSON string to specify that behavior: Example: '{ Version: 1.0, CrawlerOutput: { Partitions: { AddOrUpdateBehavior: InheritFromTable } } }'
  • craTablePrefix - The prefix added to the names of tables that are created.
  • craDescription - A description of the crawler.

craCreationTime :: Lens' Crawler (Maybe UTCTime) Source #

The time when the crawler was created.

craState :: Lens' Crawler (Maybe CrawlerState) Source #

Indicates whether the crawler is running, or whether a run is pending.

craSchemaChangePolicy :: Lens' Crawler (Maybe SchemaChangePolicy) Source #

Sets the behavior when the crawler finds a changed or deleted object.

craLastUpdated :: Lens' Crawler (Maybe UTCTime) Source #

The time the crawler was last updated.

craSchedule :: Lens' Crawler (Maybe Schedule) Source #

For scheduled crawlers, the schedule when the crawler runs.

craLastCrawl :: Lens' Crawler (Maybe LastCrawlInfo) Source #

The status of the last crawl, and potentially error information if an error occurred.

craCrawlElapsedTime :: Lens' Crawler (Maybe Integer) Source #

If the crawler is running, contains the total time elapsed since the last crawl began.

craClassifiers :: Lens' Crawler [Text] Source #

A list of custom classifiers associated with the crawler.

craRole :: Lens' Crawler (Maybe Text) Source #

The IAM role (or ARN of an IAM role) used to access customer resources, such as data in Amazon S3.

craName :: Lens' Crawler (Maybe Text) Source #

The crawler name.

craTargets :: Lens' Crawler (Maybe CrawlerTargets) Source #

A collection of targets to crawl.

craVersion :: Lens' Crawler (Maybe Integer) Source #

The version of the crawler.

craDatabaseName :: Lens' Crawler (Maybe Text) Source #

The database where metadata is written by this crawler.

craConfiguration :: Lens' Crawler (Maybe Text) Source #

Crawler configuration information. This versioned JSON string allows users to specify aspects of a Crawler's behavior. You can use this field to force partitions to inherit metadata such as classification, input format, output format, serde information, and schema from their parent table, rather than detect this information separately for each partition. Use the following JSON string to specify that behavior: Example: '{ Version: 1.0, CrawlerOutput: { Partitions: { AddOrUpdateBehavior: InheritFromTable } } }'

craTablePrefix :: Lens' Crawler (Maybe Text) Source #

The prefix added to the names of tables that are created.

craDescription :: Lens' Crawler (Maybe Text) Source #

A description of the crawler.

CrawlerMetrics

data CrawlerMetrics Source #

Metrics for a specified crawler.

See: crawlerMetrics smart constructor.

Instances

Eq CrawlerMetrics Source # 
Data CrawlerMetrics Source # 

Methods

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

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

toConstr :: CrawlerMetrics -> Constr #

dataTypeOf :: CrawlerMetrics -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CrawlerMetrics Source # 
Show CrawlerMetrics Source # 
Generic CrawlerMetrics Source # 

Associated Types

type Rep CrawlerMetrics :: * -> * #

Hashable CrawlerMetrics Source # 
FromJSON CrawlerMetrics Source # 
NFData CrawlerMetrics Source # 

Methods

rnf :: CrawlerMetrics -> () #

type Rep CrawlerMetrics Source # 
type Rep CrawlerMetrics = D1 * (MetaData "CrawlerMetrics" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CrawlerMetrics'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cmLastRuntimeSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_cmTablesCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cmStillEstimating") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_cmMedianRuntimeSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cmTimeLeftSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_cmTablesDeleted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cmTablesUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_cmCrawlerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

crawlerMetrics :: CrawlerMetrics Source #

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

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

cmLastRuntimeSeconds :: Lens' CrawlerMetrics (Maybe Double) Source #

The duration of the crawler's most recent run, in seconds.

cmTablesCreated :: Lens' CrawlerMetrics (Maybe Natural) Source #

The number of tables created by this crawler.

cmStillEstimating :: Lens' CrawlerMetrics (Maybe Bool) Source #

True if the crawler is still estimating how long it will take to complete this run.

cmMedianRuntimeSeconds :: Lens' CrawlerMetrics (Maybe Double) Source #

The median duration of this crawler's runs, in seconds.

cmTimeLeftSeconds :: Lens' CrawlerMetrics (Maybe Double) Source #

The estimated time left to complete a running crawl.

cmTablesDeleted :: Lens' CrawlerMetrics (Maybe Natural) Source #

The number of tables deleted by this crawler.

cmTablesUpdated :: Lens' CrawlerMetrics (Maybe Natural) Source #

The number of tables updated by this crawler.

cmCrawlerName :: Lens' CrawlerMetrics (Maybe Text) Source #

The name of the crawler.

CrawlerTargets

data CrawlerTargets Source #

Specifies data stores to crawl.

See: crawlerTargets smart constructor.

Instances

Eq CrawlerTargets Source # 
Data CrawlerTargets Source # 

Methods

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

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

toConstr :: CrawlerTargets -> Constr #

dataTypeOf :: CrawlerTargets -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CrawlerTargets Source # 
Show CrawlerTargets Source # 
Generic CrawlerTargets Source # 

Associated Types

type Rep CrawlerTargets :: * -> * #

Hashable CrawlerTargets Source # 
ToJSON CrawlerTargets Source # 
FromJSON CrawlerTargets Source # 
NFData CrawlerTargets Source # 

Methods

rnf :: CrawlerTargets -> () #

type Rep CrawlerTargets Source # 
type Rep CrawlerTargets = D1 * (MetaData "CrawlerTargets" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CrawlerTargets'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ctS3Targets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [S3Target]))) (S1 * (MetaSel (Just Symbol "_ctJdbcTargets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [JdbcTarget])))))

crawlerTargets :: CrawlerTargets Source #

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

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

ctS3Targets :: Lens' CrawlerTargets [S3Target] Source #

Specifies Amazon S3 targets.

ctJdbcTargets :: Lens' CrawlerTargets [JdbcTarget] Source #

Specifies JDBC targets.

CreateGrokClassifierRequest

data CreateGrokClassifierRequest Source #

Specifies a grok classifier for CreateClassifier to create.

See: createGrokClassifierRequest smart constructor.

Instances

Eq CreateGrokClassifierRequest Source # 
Data CreateGrokClassifierRequest Source # 

Methods

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

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

toConstr :: CreateGrokClassifierRequest -> Constr #

dataTypeOf :: CreateGrokClassifierRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CreateGrokClassifierRequest Source # 
Show CreateGrokClassifierRequest Source # 
Generic CreateGrokClassifierRequest Source # 
Hashable CreateGrokClassifierRequest Source # 
ToJSON CreateGrokClassifierRequest Source # 
NFData CreateGrokClassifierRequest Source # 
type Rep CreateGrokClassifierRequest Source # 
type Rep CreateGrokClassifierRequest = D1 * (MetaData "CreateGrokClassifierRequest" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CreateGrokClassifierRequest'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cgcrCustomPatterns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cgcrClassification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cgcrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cgcrGrokPattern") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

createGrokClassifierRequest Source #

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

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

  • cgcrCustomPatterns - Optional custom grok patterns used by this classifier.
  • cgcrClassification - An identifier of the data format that the classifier matches, such as Twitter, JSON, Omniture logs, Amazon CloudWatch Logs, and so on.
  • cgcrName - The name of the new classifier.
  • cgcrGrokPattern - The grok pattern used by this classifier.

cgcrCustomPatterns :: Lens' CreateGrokClassifierRequest (Maybe Text) Source #

Optional custom grok patterns used by this classifier.

cgcrClassification :: Lens' CreateGrokClassifierRequest Text Source #

An identifier of the data format that the classifier matches, such as Twitter, JSON, Omniture logs, Amazon CloudWatch Logs, and so on.

cgcrName :: Lens' CreateGrokClassifierRequest Text Source #

The name of the new classifier.

cgcrGrokPattern :: Lens' CreateGrokClassifierRequest Text Source #

The grok pattern used by this classifier.

CreateJSONClassifierRequest

data CreateJSONClassifierRequest Source #

Specifies a JSON classifier for CreateClassifier to create.

See: createJSONClassifierRequest smart constructor.

Instances

Eq CreateJSONClassifierRequest Source # 
Data CreateJSONClassifierRequest Source # 

Methods

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

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

toConstr :: CreateJSONClassifierRequest -> Constr #

dataTypeOf :: CreateJSONClassifierRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CreateJSONClassifierRequest Source # 
Show CreateJSONClassifierRequest Source # 
Generic CreateJSONClassifierRequest Source # 
Hashable CreateJSONClassifierRequest Source # 
ToJSON CreateJSONClassifierRequest Source # 
NFData CreateJSONClassifierRequest Source # 
type Rep CreateJSONClassifierRequest Source # 
type Rep CreateJSONClassifierRequest = D1 * (MetaData "CreateJSONClassifierRequest" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CreateJSONClassifierRequest'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cjcrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cjcrJSONPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

createJSONClassifierRequest Source #

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

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

cjcrName :: Lens' CreateJSONClassifierRequest Text Source #

The name of the classifier.

cjcrJSONPath :: Lens' CreateJSONClassifierRequest Text Source #

A JsonPath string defining the JSON data for the classifier to classify. AWS Glue supports a subset of JsonPath, as described in Writing JsonPath Custom Classifiers .

CreateXMLClassifierRequest

data CreateXMLClassifierRequest Source #

Specifies an XML classifier for CreateClassifier to create.

See: createXMLClassifierRequest smart constructor.

Instances

Eq CreateXMLClassifierRequest Source # 
Data CreateXMLClassifierRequest Source # 

Methods

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

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

toConstr :: CreateXMLClassifierRequest -> Constr #

dataTypeOf :: CreateXMLClassifierRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CreateXMLClassifierRequest Source # 
Show CreateXMLClassifierRequest Source # 
Generic CreateXMLClassifierRequest Source # 
Hashable CreateXMLClassifierRequest Source # 
ToJSON CreateXMLClassifierRequest Source # 
NFData CreateXMLClassifierRequest Source # 
type Rep CreateXMLClassifierRequest Source # 
type Rep CreateXMLClassifierRequest = D1 * (MetaData "CreateXMLClassifierRequest" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "CreateXMLClassifierRequest'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cxcrRowTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cxcrClassification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cxcrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

createXMLClassifierRequest Source #

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

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

  • cxcrRowTag - The XML tag designating the element that contains each record in an XML document being parsed. Note that this cannot identify a self-closing element (closed by /> ). An empty row element that contains only attributes can be parsed as long as it ends with a closing tag (for example, item_a="A" item_b="B"/row is okay, but item_a="A" item_b="B" / is not).
  • cxcrClassification - An identifier of the data format that the classifier matches.
  • cxcrName - The name of the classifier.

cxcrRowTag :: Lens' CreateXMLClassifierRequest (Maybe Text) Source #

The XML tag designating the element that contains each record in an XML document being parsed. Note that this cannot identify a self-closing element (closed by /> ). An empty row element that contains only attributes can be parsed as long as it ends with a closing tag (for example, item_a="A" item_b="B"/row is okay, but item_a="A" item_b="B" / is not).

cxcrClassification :: Lens' CreateXMLClassifierRequest Text Source #

An identifier of the data format that the classifier matches.

cxcrName :: Lens' CreateXMLClassifierRequest Text Source #

The name of the classifier.

Database

data Database Source #

The Database object represents a logical grouping of tables that may reside in a Hive metastore or an RDBMS.

See: database smart constructor.

Instances

Eq Database Source # 
Data Database Source # 

Methods

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

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

toConstr :: Database -> Constr #

dataTypeOf :: Database -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Database Source # 
Show Database Source # 
Generic Database Source # 

Associated Types

type Rep Database :: * -> * #

Methods

from :: Database -> Rep Database x #

to :: Rep Database x -> Database #

Hashable Database Source # 

Methods

hashWithSalt :: Int -> Database -> Int #

hash :: Database -> Int #

FromJSON Database Source # 
NFData Database Source # 

Methods

rnf :: Database -> () #

type Rep Database Source # 
type Rep Database = D1 * (MetaData "Database" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Database'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dLocationURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_dName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))))

database Source #

Arguments

:: Text

dName

-> Database 

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

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

  • dLocationURI - The location of the database (for example, an HDFS path).
  • dParameters - A list of key-value pairs that define parameters and properties of the database.
  • dDescription - Description of the database.
  • dCreateTime - The time at which the metadata database was created in the catalog.
  • dName - Name of the database. For Hive compatibility, this is folded to lowercase when it is stored.

dLocationURI :: Lens' Database (Maybe Text) Source #

The location of the database (for example, an HDFS path).

dParameters :: Lens' Database (HashMap Text Text) Source #

A list of key-value pairs that define parameters and properties of the database.

dDescription :: Lens' Database (Maybe Text) Source #

Description of the database.

dCreateTime :: Lens' Database (Maybe UTCTime) Source #

The time at which the metadata database was created in the catalog.

dName :: Lens' Database Text Source #

Name of the database. For Hive compatibility, this is folded to lowercase when it is stored.

DatabaseInput

data DatabaseInput Source #

The structure used to create or update a database.

See: databaseInput smart constructor.

Instances

Eq DatabaseInput Source # 
Data DatabaseInput Source # 

Methods

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

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

toConstr :: DatabaseInput -> Constr #

dataTypeOf :: DatabaseInput -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatabaseInput Source # 
Show DatabaseInput Source # 
Generic DatabaseInput Source # 

Associated Types

type Rep DatabaseInput :: * -> * #

Hashable DatabaseInput Source # 
ToJSON DatabaseInput Source # 
NFData DatabaseInput Source # 

Methods

rnf :: DatabaseInput -> () #

type Rep DatabaseInput Source # 
type Rep DatabaseInput = D1 * (MetaData "DatabaseInput" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "DatabaseInput'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_diLocationURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_diParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_diDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_diName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

databaseInput Source #

Arguments

:: Text

diName

-> DatabaseInput 

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

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

  • diLocationURI - The location of the database (for example, an HDFS path).
  • diParameters - A list of key-value pairs that define parameters and properties of the database.
  • diDescription - Description of the database
  • diName - Name of the database. For Hive compatibility, this is folded to lowercase when it is stored.

diLocationURI :: Lens' DatabaseInput (Maybe Text) Source #

The location of the database (for example, an HDFS path).

diParameters :: Lens' DatabaseInput (HashMap Text Text) Source #

A list of key-value pairs that define parameters and properties of the database.

diDescription :: Lens' DatabaseInput (Maybe Text) Source #

Description of the database

diName :: Lens' DatabaseInput Text Source #

Name of the database. For Hive compatibility, this is folded to lowercase when it is stored.

DevEndpoint

data DevEndpoint Source #

A development endpoint where a developer can remotely debug ETL scripts.

See: devEndpoint smart constructor.

Instances

Eq DevEndpoint Source # 
Data DevEndpoint Source # 

Methods

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

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

toConstr :: DevEndpoint -> Constr #

dataTypeOf :: DevEndpoint -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DevEndpoint Source # 
Show DevEndpoint Source # 
Generic DevEndpoint Source # 

Associated Types

type Rep DevEndpoint :: * -> * #

Hashable DevEndpoint Source # 
FromJSON DevEndpoint Source # 
NFData DevEndpoint Source # 

Methods

rnf :: DevEndpoint -> () #

type Rep DevEndpoint Source # 
type Rep DevEndpoint = D1 * (MetaData "DevEndpoint" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "DevEndpoint'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_deStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_deFailureReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_deEndpointName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_deExtraPythonLibsS3Path") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_deLastUpdateStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_deSecurityGroupIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_deLastModifiedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_deVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dePrivateAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dePublicKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_deSubnetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_deNumberOfNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dePublicAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_deAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_deZeppelinRemoteSparkInterpreterPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_deExtraJARsS3Path") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_deCreatedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_deYarnEndpointAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_deRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))))

devEndpoint :: DevEndpoint Source #

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

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

  • deStatus - The current status of this DevEndpoint.
  • deFailureReason - The reason for a current failure in this DevEndpoint.
  • deEndpointName - The name of the DevEndpoint.
  • deExtraPythonLibsS3Path - Path(s) to one or more Python libraries in an S3 bucket that should be loaded in your DevEndpoint. Multiple values must be complete paths separated by a comma. Please note that only pure Python libraries can currently be used on a DevEndpoint. Libraries that rely on C extensions, such as the pandas Python data analysis library, are not yet supported.
  • deLastUpdateStatus - The status of the last update.
  • deSecurityGroupIds - A list of security group identifiers used in this DevEndpoint.
  • deLastModifiedTimestamp - The point in time at which this DevEndpoint was last modified.
  • deVPCId - The ID of the virtual private cloud (VPC) used by this DevEndpoint.
  • dePrivateAddress - The private address used by this DevEndpoint.
  • dePublicKey - The public key to be used by this DevEndpoint for authentication.
  • deSubnetId - The subnet ID for this DevEndpoint.
  • deNumberOfNodes - The number of AWS Glue Data Processing Units (DPUs) allocated to this DevEndpoint.
  • dePublicAddress - The public VPC address used by this DevEndpoint.
  • deAvailabilityZone - The AWS availability zone where this DevEndpoint is located.
  • deZeppelinRemoteSparkInterpreterPort - The Apache Zeppelin port for the remote Apache Spark interpreter.
  • deExtraJARsS3Path - Path to one or more Java Jars in an S3 bucket that should be loaded in your DevEndpoint. Please note that only pure Java/Scala libraries can currently be used on a DevEndpoint.
  • deCreatedTimestamp - The point in time at which this DevEndpoint was created.
  • deYarnEndpointAddress - The YARN endpoint address used by this DevEndpoint.
  • deRoleARN - The AWS ARN of the IAM role used in this DevEndpoint.

deStatus :: Lens' DevEndpoint (Maybe Text) Source #

The current status of this DevEndpoint.

deFailureReason :: Lens' DevEndpoint (Maybe Text) Source #

The reason for a current failure in this DevEndpoint.

deEndpointName :: Lens' DevEndpoint (Maybe Text) Source #

The name of the DevEndpoint.

deExtraPythonLibsS3Path :: Lens' DevEndpoint (Maybe Text) Source #

Path(s) to one or more Python libraries in an S3 bucket that should be loaded in your DevEndpoint. Multiple values must be complete paths separated by a comma. Please note that only pure Python libraries can currently be used on a DevEndpoint. Libraries that rely on C extensions, such as the pandas Python data analysis library, are not yet supported.

deLastUpdateStatus :: Lens' DevEndpoint (Maybe Text) Source #

The status of the last update.

deSecurityGroupIds :: Lens' DevEndpoint [Text] Source #

A list of security group identifiers used in this DevEndpoint.

deLastModifiedTimestamp :: Lens' DevEndpoint (Maybe UTCTime) Source #

The point in time at which this DevEndpoint was last modified.

deVPCId :: Lens' DevEndpoint (Maybe Text) Source #

The ID of the virtual private cloud (VPC) used by this DevEndpoint.

dePrivateAddress :: Lens' DevEndpoint (Maybe Text) Source #

The private address used by this DevEndpoint.

dePublicKey :: Lens' DevEndpoint (Maybe Text) Source #

The public key to be used by this DevEndpoint for authentication.

deSubnetId :: Lens' DevEndpoint (Maybe Text) Source #

The subnet ID for this DevEndpoint.

deNumberOfNodes :: Lens' DevEndpoint (Maybe Int) Source #

The number of AWS Glue Data Processing Units (DPUs) allocated to this DevEndpoint.

dePublicAddress :: Lens' DevEndpoint (Maybe Text) Source #

The public VPC address used by this DevEndpoint.

deAvailabilityZone :: Lens' DevEndpoint (Maybe Text) Source #

The AWS availability zone where this DevEndpoint is located.

deZeppelinRemoteSparkInterpreterPort :: Lens' DevEndpoint (Maybe Int) Source #

The Apache Zeppelin port for the remote Apache Spark interpreter.

deExtraJARsS3Path :: Lens' DevEndpoint (Maybe Text) Source #

Path to one or more Java Jars in an S3 bucket that should be loaded in your DevEndpoint. Please note that only pure Java/Scala libraries can currently be used on a DevEndpoint.

deCreatedTimestamp :: Lens' DevEndpoint (Maybe UTCTime) Source #

The point in time at which this DevEndpoint was created.

deYarnEndpointAddress :: Lens' DevEndpoint (Maybe Text) Source #

The YARN endpoint address used by this DevEndpoint.

deRoleARN :: Lens' DevEndpoint (Maybe Text) Source #

The AWS ARN of the IAM role used in this DevEndpoint.

DevEndpointCustomLibraries

data DevEndpointCustomLibraries Source #

Custom libraries to be loaded into a DevEndpoint.

See: devEndpointCustomLibraries smart constructor.

Instances

Eq DevEndpointCustomLibraries Source # 
Data DevEndpointCustomLibraries Source # 

Methods

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

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

toConstr :: DevEndpointCustomLibraries -> Constr #

dataTypeOf :: DevEndpointCustomLibraries -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DevEndpointCustomLibraries Source # 
Show DevEndpointCustomLibraries Source # 
Generic DevEndpointCustomLibraries Source # 
Hashable DevEndpointCustomLibraries Source # 
ToJSON DevEndpointCustomLibraries Source # 
NFData DevEndpointCustomLibraries Source # 
type Rep DevEndpointCustomLibraries Source # 
type Rep DevEndpointCustomLibraries = D1 * (MetaData "DevEndpointCustomLibraries" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "DevEndpointCustomLibraries'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_declExtraPythonLibsS3Path") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_declExtraJARsS3Path") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

devEndpointCustomLibraries :: DevEndpointCustomLibraries Source #

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

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

  • declExtraPythonLibsS3Path - Path(s) to one or more Python libraries in an S3 bucket that should be loaded in your DevEndpoint. Multiple values must be complete paths separated by a comma. Please note that only pure Python libraries can currently be used on a DevEndpoint. Libraries that rely on C extensions, such as the pandas Python data analysis library, are not yet supported.
  • declExtraJARsS3Path - Path to one or more Java Jars in an S3 bucket that should be loaded in your DevEndpoint. Please note that only pure Java/Scala libraries can currently be used on a DevEndpoint.

declExtraPythonLibsS3Path :: Lens' DevEndpointCustomLibraries (Maybe Text) Source #

Path(s) to one or more Python libraries in an S3 bucket that should be loaded in your DevEndpoint. Multiple values must be complete paths separated by a comma. Please note that only pure Python libraries can currently be used on a DevEndpoint. Libraries that rely on C extensions, such as the pandas Python data analysis library, are not yet supported.

declExtraJARsS3Path :: Lens' DevEndpointCustomLibraries (Maybe Text) Source #

Path to one or more Java Jars in an S3 bucket that should be loaded in your DevEndpoint. Please note that only pure Java/Scala libraries can currently be used on a DevEndpoint.

ErrorDetail

data ErrorDetail Source #

Contains details about an error.

See: errorDetail smart constructor.

Instances

Eq ErrorDetail Source # 
Data ErrorDetail Source # 

Methods

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

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

toConstr :: ErrorDetail -> Constr #

dataTypeOf :: ErrorDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ErrorDetail Source # 
Show ErrorDetail Source # 
Generic ErrorDetail Source # 

Associated Types

type Rep ErrorDetail :: * -> * #

Hashable ErrorDetail Source # 
FromJSON ErrorDetail Source # 
NFData ErrorDetail Source # 

Methods

rnf :: ErrorDetail -> () #

type Rep ErrorDetail Source # 
type Rep ErrorDetail = D1 * (MetaData "ErrorDetail" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "ErrorDetail'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_edErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_edErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

errorDetail :: ErrorDetail Source #

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

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

edErrorCode :: Lens' ErrorDetail (Maybe Text) Source #

The code associated with this error.

edErrorMessage :: Lens' ErrorDetail (Maybe Text) Source #

A message describing the error.

ExecutionProperty

data ExecutionProperty Source #

An execution property of a job.

See: executionProperty smart constructor.

Instances

Eq ExecutionProperty Source # 
Data ExecutionProperty Source # 

Methods

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

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

toConstr :: ExecutionProperty -> Constr #

dataTypeOf :: ExecutionProperty -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ExecutionProperty -> () #

type Rep ExecutionProperty Source # 
type Rep ExecutionProperty = D1 * (MetaData "ExecutionProperty" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" True) (C1 * (MetaCons "ExecutionProperty'" PrefixI True) (S1 * (MetaSel (Just Symbol "_epMaxConcurrentRuns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))))

executionProperty :: ExecutionProperty Source #

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

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

  • epMaxConcurrentRuns - The maximum number of concurrent runs allowed for the job. The default is 1. An error is returned when this threshold is reached. The maximum value you can specify is controlled by a service limit.

epMaxConcurrentRuns :: Lens' ExecutionProperty (Maybe Int) Source #

The maximum number of concurrent runs allowed for the job. The default is 1. An error is returned when this threshold is reached. The maximum value you can specify is controlled by a service limit.

GetConnectionsFilter

data GetConnectionsFilter Source #

Filters the connection definitions returned by the GetConnections API.

See: getConnectionsFilter smart constructor.

Instances

Eq GetConnectionsFilter Source # 
Data GetConnectionsFilter Source # 

Methods

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

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

toConstr :: GetConnectionsFilter -> Constr #

dataTypeOf :: GetConnectionsFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GetConnectionsFilter -> () #

type Rep GetConnectionsFilter Source # 
type Rep GetConnectionsFilter = D1 * (MetaData "GetConnectionsFilter" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "GetConnectionsFilter'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_gcfMatchCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_gcfConnectionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ConnectionType)))))

getConnectionsFilter :: GetConnectionsFilter Source #

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

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

  • gcfMatchCriteria - A criteria string that must match the criteria recorded in the connection definition for that connection definition to be returned.
  • gcfConnectionType - The type of connections to return. Currently, only JDBC is supported; SFTP is not supported.

gcfMatchCriteria :: Lens' GetConnectionsFilter [Text] Source #

A criteria string that must match the criteria recorded in the connection definition for that connection definition to be returned.

gcfConnectionType :: Lens' GetConnectionsFilter (Maybe ConnectionType) Source #

The type of connections to return. Currently, only JDBC is supported; SFTP is not supported.

GrokClassifier

data GrokClassifier Source #

A classifier that uses grok patterns.

See: grokClassifier smart constructor.

Instances

Eq GrokClassifier Source # 
Data GrokClassifier Source # 

Methods

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

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

toConstr :: GrokClassifier -> Constr #

dataTypeOf :: GrokClassifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GrokClassifier Source # 
Show GrokClassifier Source # 
Generic GrokClassifier Source # 

Associated Types

type Rep GrokClassifier :: * -> * #

Hashable GrokClassifier Source # 
FromJSON GrokClassifier Source # 
NFData GrokClassifier Source # 

Methods

rnf :: GrokClassifier -> () #

type Rep GrokClassifier Source # 

grokClassifier Source #

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

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

gcCreationTime :: Lens' GrokClassifier (Maybe UTCTime) Source #

The time this classifier was registered.

gcLastUpdated :: Lens' GrokClassifier (Maybe UTCTime) Source #

The time this classifier was last updated.

gcVersion :: Lens' GrokClassifier (Maybe Integer) Source #

The version of this classifier.

gcCustomPatterns :: Lens' GrokClassifier (Maybe Text) Source #

Optional custom grok patterns defined by this classifier. For more information, see custom patterns in Writing Custom Classifers .

gcName :: Lens' GrokClassifier Text Source #

The name of the classifier.

gcClassification :: Lens' GrokClassifier Text Source #

An identifier of the data format that the classifier matches, such as Twitter, JSON, Omniture logs, and so on.

gcGrokPattern :: Lens' GrokClassifier Text Source #

The grok pattern applied to a data store by this classifier. For more information, see built-in patterns in Writing Custom Classifers .

JSONClassifier

data JSONClassifier Source #

A classifier for JSON content.

See: jsonClassifier smart constructor.

Instances

Eq JSONClassifier Source # 
Data JSONClassifier Source # 

Methods

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

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

toConstr :: JSONClassifier -> Constr #

dataTypeOf :: JSONClassifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JSONClassifier Source # 
Show JSONClassifier Source # 
Generic JSONClassifier Source # 

Associated Types

type Rep JSONClassifier :: * -> * #

Hashable JSONClassifier Source # 
FromJSON JSONClassifier Source # 
NFData JSONClassifier Source # 

Methods

rnf :: JSONClassifier -> () #

type Rep JSONClassifier Source # 
type Rep JSONClassifier = D1 * (MetaData "JSONClassifier" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "JSONClassifier'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jcCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_jcLastUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jcVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_jcJSONPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))))

jsonClassifier Source #

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

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

jcCreationTime :: Lens' JSONClassifier (Maybe UTCTime) Source #

The time this classifier was registered.

jcLastUpdated :: Lens' JSONClassifier (Maybe UTCTime) Source #

The time this classifier was last updated.

jcVersion :: Lens' JSONClassifier (Maybe Integer) Source #

The version of this classifier.

jcName :: Lens' JSONClassifier Text Source #

The name of the classifier.

jcJSONPath :: Lens' JSONClassifier Text Source #

A JsonPath string defining the JSON data for the classifier to classify. AWS Glue supports a subset of JsonPath, as described in Writing JsonPath Custom Classifiers .

JdbcTarget

data JdbcTarget Source #

Specifies a JDBC data store to crawl.

See: jdbcTarget smart constructor.

Instances

Eq JdbcTarget Source # 
Data JdbcTarget Source # 

Methods

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

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

toConstr :: JdbcTarget -> Constr #

dataTypeOf :: JdbcTarget -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JdbcTarget Source # 
Show JdbcTarget Source # 
Generic JdbcTarget Source # 

Associated Types

type Rep JdbcTarget :: * -> * #

Hashable JdbcTarget Source # 
ToJSON JdbcTarget Source # 
FromJSON JdbcTarget Source # 
NFData JdbcTarget Source # 

Methods

rnf :: JdbcTarget -> () #

type Rep JdbcTarget Source # 
type Rep JdbcTarget = D1 * (MetaData "JdbcTarget" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "JdbcTarget'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_jtPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jtConnectionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jtExclusions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))))))

jdbcTarget :: JdbcTarget Source #

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

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

jtPath :: Lens' JdbcTarget (Maybe Text) Source #

The path of the JDBC target.

jtConnectionName :: Lens' JdbcTarget (Maybe Text) Source #

The name of the connection to use to connect to the JDBC target.

jtExclusions :: Lens' JdbcTarget [Text] Source #

A list of glob patterns used to exclude from the crawl. For more information, see Catalog Tables with a Crawler .

Job

data Job Source #

Specifies a job definition.

See: job smart constructor.

Instances

Eq Job Source # 

Methods

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

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

Data Job Source # 

Methods

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

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

toConstr :: Job -> Constr #

dataTypeOf :: Job -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Job Source # 
Show Job Source # 

Methods

showsPrec :: Int -> Job -> ShowS #

show :: Job -> String #

showList :: [Job] -> ShowS #

Generic Job Source # 

Associated Types

type Rep Job :: * -> * #

Methods

from :: Job -> Rep Job x #

to :: Rep Job x -> Job #

Hashable Job Source # 

Methods

hashWithSalt :: Int -> Job -> Int #

hash :: Job -> Int #

FromJSON Job Source # 
NFData Job Source # 

Methods

rnf :: Job -> () #

type Rep Job Source # 
type Rep Job = D1 * (MetaData "Job" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Job'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jCommand") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe JobCommand))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jLastModifiedOn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_jConnections") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ConnectionsList))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jLogURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jMaxRetries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jExecutionProperty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ExecutionProperty))) (S1 * (MetaSel (Just Symbol "_jAllocatedCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jTimeout") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_jDefaultArguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jCreatedOn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))))

job :: Job Source #

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

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

  • jCommand - The JobCommand that executes this job.
  • jLastModifiedOn - The last point in time when this job definition was modified.
  • jConnections - The connections used for this job.
  • jRole - The name or ARN of the IAM role associated with this job.
  • jName - The name you assign to this job definition.
  • jLogURI - This field is reserved for future use.
  • jMaxRetries - The maximum number of times to retry this job after a JobRun fails.
  • jExecutionProperty - An ExecutionProperty specifying the maximum number of concurrent runs allowed for this job.
  • jAllocatedCapacity - The number of AWS Glue data processing units (DPUs) allocated to runs of this job. From 2 to 100 DPUs can be allocated; the default is 10. A DPU is a relative measure of processing power that consists of 4 vCPUs of compute capacity and 16 GB of memory. For more information, see the AWS Glue pricing page .
  • jTimeout - The job timeout in minutes.
  • jDefaultArguments - The default arguments for this job, specified as name-value pairs. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own Job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.
  • jDescription - Description of the job being defined.
  • jCreatedOn - The time and date that this job definition was created.

jCommand :: Lens' Job (Maybe JobCommand) Source #

The JobCommand that executes this job.

jLastModifiedOn :: Lens' Job (Maybe UTCTime) Source #

The last point in time when this job definition was modified.

jConnections :: Lens' Job (Maybe ConnectionsList) Source #

The connections used for this job.

jRole :: Lens' Job (Maybe Text) Source #

The name or ARN of the IAM role associated with this job.

jName :: Lens' Job (Maybe Text) Source #

The name you assign to this job definition.

jLogURI :: Lens' Job (Maybe Text) Source #

This field is reserved for future use.

jMaxRetries :: Lens' Job (Maybe Int) Source #

The maximum number of times to retry this job after a JobRun fails.

jExecutionProperty :: Lens' Job (Maybe ExecutionProperty) Source #

An ExecutionProperty specifying the maximum number of concurrent runs allowed for this job.

jAllocatedCapacity :: Lens' Job (Maybe Int) Source #

The number of AWS Glue data processing units (DPUs) allocated to runs of this job. From 2 to 100 DPUs can be allocated; the default is 10. A DPU is a relative measure of processing power that consists of 4 vCPUs of compute capacity and 16 GB of memory. For more information, see the AWS Glue pricing page .

jTimeout :: Lens' Job (Maybe Natural) Source #

The job timeout in minutes.

jDefaultArguments :: Lens' Job (HashMap Text Text) Source #

The default arguments for this job, specified as name-value pairs. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own Job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.

jDescription :: Lens' Job (Maybe Text) Source #

Description of the job being defined.

jCreatedOn :: Lens' Job (Maybe UTCTime) Source #

The time and date that this job definition was created.

JobBookmarkEntry

data JobBookmarkEntry Source #

Defines a point which a job can resume processing.

See: jobBookmarkEntry smart constructor.

Instances

Eq JobBookmarkEntry Source # 
Data JobBookmarkEntry Source # 

Methods

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

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

toConstr :: JobBookmarkEntry -> Constr #

dataTypeOf :: JobBookmarkEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: JobBookmarkEntry -> () #

type Rep JobBookmarkEntry Source # 
type Rep JobBookmarkEntry = D1 * (MetaData "JobBookmarkEntry" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "JobBookmarkEntry'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jbeJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jbeRun") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jbeVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jbeAttempt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_jbeJobBookmark") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

jobBookmarkEntry :: JobBookmarkEntry Source #

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

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

jbeJobName :: Lens' JobBookmarkEntry (Maybe Text) Source #

Name of the job in question.

jbeRun :: Lens' JobBookmarkEntry (Maybe Int) Source #

The run ID number.

jbeAttempt :: Lens' JobBookmarkEntry (Maybe Int) Source #

The attempt ID number.

JobCommand

data JobCommand Source #

Specifies code executed when a job is run.

See: jobCommand smart constructor.

Instances

Eq JobCommand Source # 
Data JobCommand Source # 

Methods

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

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

toConstr :: JobCommand -> Constr #

dataTypeOf :: JobCommand -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobCommand Source # 
Show JobCommand Source # 
Generic JobCommand Source # 

Associated Types

type Rep JobCommand :: * -> * #

Hashable JobCommand Source # 
ToJSON JobCommand Source # 
FromJSON JobCommand Source # 
NFData JobCommand Source # 

Methods

rnf :: JobCommand -> () #

type Rep JobCommand Source # 
type Rep JobCommand = D1 * (MetaData "JobCommand" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "JobCommand'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_jobScriptLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

jobCommand :: JobCommand Source #

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

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

  • jobScriptLocation - Specifies the S3 path to a script that executes a job (required).
  • jobName - The name of the job command: this must be glueetl .

jobScriptLocation :: Lens' JobCommand (Maybe Text) Source #

Specifies the S3 path to a script that executes a job (required).

jobName :: Lens' JobCommand (Maybe Text) Source #

The name of the job command: this must be glueetl .

JobRun

data JobRun Source #

Contains information about a job run.

See: jobRun smart constructor.

Instances

Eq JobRun Source # 

Methods

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

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

Data JobRun Source # 

Methods

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

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

toConstr :: JobRun -> Constr #

dataTypeOf :: JobRun -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobRun Source # 
Show JobRun Source # 
Generic JobRun Source # 

Associated Types

type Rep JobRun :: * -> * #

Methods

from :: JobRun -> Rep JobRun x #

to :: Rep JobRun x -> JobRun #

Hashable JobRun Source # 

Methods

hashWithSalt :: Int -> JobRun -> Int #

hash :: JobRun -> Int #

FromJSON JobRun Source # 
NFData JobRun Source # 

Methods

rnf :: JobRun -> () #

type Rep JobRun Source # 
type Rep JobRun = D1 * (MetaData "JobRun" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "JobRun'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jrCompletedOn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jrTriggerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jrLastModifiedOn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jrArguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) (S1 * (MetaSel (Just Symbol "_jrJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jrStartedOn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_jrJobRunState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe JobRunState)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jrExecutionTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_jrPredecessorRuns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Predecessor])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jrPreviousRunId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_jrId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_jrAttempt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_jrAllocatedCapacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_jrTimeout") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_jrErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

jobRun :: JobRun Source #

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

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

  • jrCompletedOn - The date and time this job run completed.
  • jrTriggerName - The name of the trigger that started this job run.
  • jrLastModifiedOn - The last time this job run was modified.
  • jrArguments - The job arguments associated with this run. These override equivalent default arguments set for the job. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.
  • jrJobName - The name of the job definition being used in this run.
  • jrStartedOn - The date and time at which this job run was started.
  • jrJobRunState - The current state of the job run.
  • jrExecutionTime - The amount of time (in seconds) that the job run consumed resources.
  • jrPredecessorRuns - A list of predecessors to this job run.
  • jrPreviousRunId - The ID of the previous run of this job. For example, the JobRunId specified in the StartJobRun action.
  • jrId - The ID of this job run.
  • jrAttempt - The number of the attempt to run this job.
  • jrAllocatedCapacity - The number of AWS Glue data processing units (DPUs) allocated to this JobRun. From 2 to 100 DPUs can be allocated; the default is 10. A DPU is a relative measure of processing power that consists of 4 vCPUs of compute capacity and 16 GB of memory. For more information, see the AWS Glue pricing page .
  • jrTimeout - The job run timeout in minutes.
  • jrErrorMessage - An error message associated with this job run.

jrCompletedOn :: Lens' JobRun (Maybe UTCTime) Source #

The date and time this job run completed.

jrTriggerName :: Lens' JobRun (Maybe Text) Source #

The name of the trigger that started this job run.

jrLastModifiedOn :: Lens' JobRun (Maybe UTCTime) Source #

The last time this job run was modified.

jrArguments :: Lens' JobRun (HashMap Text Text) Source #

The job arguments associated with this run. These override equivalent default arguments set for the job. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.

jrJobName :: Lens' JobRun (Maybe Text) Source #

The name of the job definition being used in this run.

jrStartedOn :: Lens' JobRun (Maybe UTCTime) Source #

The date and time at which this job run was started.

jrJobRunState :: Lens' JobRun (Maybe JobRunState) Source #

The current state of the job run.

jrExecutionTime :: Lens' JobRun (Maybe Int) Source #

The amount of time (in seconds) that the job run consumed resources.

jrPredecessorRuns :: Lens' JobRun [Predecessor] Source #

A list of predecessors to this job run.

jrPreviousRunId :: Lens' JobRun (Maybe Text) Source #

The ID of the previous run of this job. For example, the JobRunId specified in the StartJobRun action.

jrId :: Lens' JobRun (Maybe Text) Source #

The ID of this job run.

jrAttempt :: Lens' JobRun (Maybe Int) Source #

The number of the attempt to run this job.

jrAllocatedCapacity :: Lens' JobRun (Maybe Int) Source #

The number of AWS Glue data processing units (DPUs) allocated to this JobRun. From 2 to 100 DPUs can be allocated; the default is 10. A DPU is a relative measure of processing power that consists of 4 vCPUs of compute capacity and 16 GB of memory. For more information, see the AWS Glue pricing page .

jrTimeout :: Lens' JobRun (Maybe Natural) Source #

The job run timeout in minutes.

jrErrorMessage :: Lens' JobRun (Maybe Text) Source #

An error message associated with this job run.

JobUpdate

data JobUpdate Source #

Specifies information used to update an existing job definition. Note that the previous job definition will be completely overwritten by this information.

See: jobUpdate smart constructor.

Instances

Eq JobUpdate Source # 
Data JobUpdate Source # 

Methods

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

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

toConstr :: JobUpdate -> Constr #

dataTypeOf :: JobUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read JobUpdate Source # 
Show JobUpdate Source # 
Generic JobUpdate Source # 

Associated Types

type Rep JobUpdate :: * -> * #

Hashable JobUpdate Source # 
ToJSON JobUpdate Source # 
NFData JobUpdate Source # 

Methods

rnf :: JobUpdate -> () #

type Rep JobUpdate Source # 

jobUpdate :: JobUpdate Source #

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

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

  • juCommand - The JobCommand that executes this job (required).
  • juConnections - The connections used for this job.
  • juRole - The name or ARN of the IAM role associated with this job (required).
  • juLogURI - This field is reserved for future use.
  • juMaxRetries - The maximum number of times to retry this job if it fails.
  • juExecutionProperty - An ExecutionProperty specifying the maximum number of concurrent runs allowed for this job.
  • juAllocatedCapacity - The number of AWS Glue data processing units (DPUs) to allocate to this Job. From 2 to 100 DPUs can be allocated; the default is 10. A DPU is a relative measure of processing power that consists of 4 vCPUs of compute capacity and 16 GB of memory. For more information, see the AWS Glue pricing page .
  • juTimeout - The job timeout in minutes. The default is 2880 minutes (48 hours).
  • juDefaultArguments - The default arguments for this job. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own Job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.
  • juDescription - Description of the job being defined.

juCommand :: Lens' JobUpdate (Maybe JobCommand) Source #

The JobCommand that executes this job (required).

juConnections :: Lens' JobUpdate (Maybe ConnectionsList) Source #

The connections used for this job.

juRole :: Lens' JobUpdate (Maybe Text) Source #

The name or ARN of the IAM role associated with this job (required).

juLogURI :: Lens' JobUpdate (Maybe Text) Source #

This field is reserved for future use.

juMaxRetries :: Lens' JobUpdate (Maybe Int) Source #

The maximum number of times to retry this job if it fails.

juExecutionProperty :: Lens' JobUpdate (Maybe ExecutionProperty) Source #

An ExecutionProperty specifying the maximum number of concurrent runs allowed for this job.

juAllocatedCapacity :: Lens' JobUpdate (Maybe Int) Source #

The number of AWS Glue data processing units (DPUs) to allocate to this Job. From 2 to 100 DPUs can be allocated; the default is 10. A DPU is a relative measure of processing power that consists of 4 vCPUs of compute capacity and 16 GB of memory. For more information, see the AWS Glue pricing page .

juTimeout :: Lens' JobUpdate (Maybe Natural) Source #

The job timeout in minutes. The default is 2880 minutes (48 hours).

juDefaultArguments :: Lens' JobUpdate (HashMap Text Text) Source #

The default arguments for this job. You can specify arguments here that your own job-execution script consumes, as well as arguments that AWS Glue itself consumes. For information about how to specify and consume your own Job arguments, see the Calling AWS Glue APIs in Python topic in the developer guide. For information about the key-value pairs that AWS Glue consumes to set up your job, see the Special Parameters Used by AWS Glue topic in the developer guide.

juDescription :: Lens' JobUpdate (Maybe Text) Source #

Description of the job being defined.

LastCrawlInfo

data LastCrawlInfo Source #

Status and error information about the most recent crawl.

See: lastCrawlInfo smart constructor.

Instances

Eq LastCrawlInfo Source # 
Data LastCrawlInfo Source # 

Methods

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

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

toConstr :: LastCrawlInfo -> Constr #

dataTypeOf :: LastCrawlInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LastCrawlInfo Source # 
Show LastCrawlInfo Source # 
Generic LastCrawlInfo Source # 

Associated Types

type Rep LastCrawlInfo :: * -> * #

Hashable LastCrawlInfo Source # 
FromJSON LastCrawlInfo Source # 
NFData LastCrawlInfo Source # 

Methods

rnf :: LastCrawlInfo -> () #

type Rep LastCrawlInfo Source # 
type Rep LastCrawlInfo = D1 * (MetaData "LastCrawlInfo" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "LastCrawlInfo'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lciStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LastCrawlStatus))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lciStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_lciLogStream") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lciLogGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lciMessagePrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lciErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

lastCrawlInfo :: LastCrawlInfo Source #

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

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

lciStatus :: Lens' LastCrawlInfo (Maybe LastCrawlStatus) Source #

Status of the last crawl.

lciStartTime :: Lens' LastCrawlInfo (Maybe UTCTime) Source #

The time at which the crawl started.

lciLogStream :: Lens' LastCrawlInfo (Maybe Text) Source #

The log stream for the last crawl.

lciLogGroup :: Lens' LastCrawlInfo (Maybe Text) Source #

The log group for the last crawl.

lciMessagePrefix :: Lens' LastCrawlInfo (Maybe Text) Source #

The prefix for a message about this crawl.

lciErrorMessage :: Lens' LastCrawlInfo (Maybe Text) Source #

If an error occurred, the error information about the last crawl.

Location

data Location Source #

The location of resources.

See: location smart constructor.

Instances

Eq Location Source # 
Data Location Source # 

Methods

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

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

toConstr :: Location -> Constr #

dataTypeOf :: Location -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Location Source # 
Show Location Source # 
Generic Location Source # 

Associated Types

type Rep Location :: * -> * #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

Hashable Location Source # 

Methods

hashWithSalt :: Int -> Location -> Int #

hash :: Location -> Int #

ToJSON Location Source # 
NFData Location Source # 

Methods

rnf :: Location -> () #

type Rep Location Source # 
type Rep Location = D1 * (MetaData "Location" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Location'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lJdbc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [CodeGenNodeArg]))) (S1 * (MetaSel (Just Symbol "_lS3") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [CodeGenNodeArg])))))

location :: Location Source #

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

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

  • lJdbc - A JDBC location.
  • lS3 - An Amazon S3 location.

lJdbc :: Lens' Location [CodeGenNodeArg] Source #

A JDBC location.

lS3 :: Lens' Location [CodeGenNodeArg] Source #

An Amazon S3 location.

MappingEntry

data MappingEntry Source #

Defines a mapping.

See: mappingEntry smart constructor.

Instances

Eq MappingEntry Source # 
Data MappingEntry Source # 

Methods

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

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

toConstr :: MappingEntry -> Constr #

dataTypeOf :: MappingEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MappingEntry Source # 
Show MappingEntry Source # 
Generic MappingEntry Source # 

Associated Types

type Rep MappingEntry :: * -> * #

Hashable MappingEntry Source # 
ToJSON MappingEntry Source # 
FromJSON MappingEntry Source # 
NFData MappingEntry Source # 

Methods

rnf :: MappingEntry -> () #

type Rep MappingEntry Source # 
type Rep MappingEntry = D1 * (MetaData "MappingEntry" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "MappingEntry'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_meTargetTable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_meSourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_meSourceTable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_meTargetType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_meTargetPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_meSourcePath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

mappingEntry :: MappingEntry Source #

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

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

meSourceTable :: Lens' MappingEntry (Maybe Text) Source #

The name of the source table.

Order

data Order Source #

Specifies the sort order of a sorted column.

See: order smart constructor.

Instances

Eq Order Source # 

Methods

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

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

Data Order Source # 

Methods

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

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

toConstr :: Order -> Constr #

dataTypeOf :: Order -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Order Source # 
Show Order Source # 

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Generic Order Source # 

Associated Types

type Rep Order :: * -> * #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

Hashable Order Source # 

Methods

hashWithSalt :: Int -> Order -> Int #

hash :: Order -> Int #

ToJSON Order Source # 
FromJSON Order Source # 
NFData Order Source # 

Methods

rnf :: Order -> () #

type Rep Order Source # 
type Rep Order = D1 * (MetaData "Order" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Order'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_oColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_oSortOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat))))

order Source #

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

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

  • oColumn - The name of the column.
  • oSortOrder - Indicates that the column is sorted in ascending order (== 1 ), or in descending order (==0 ).

oColumn :: Lens' Order Text Source #

The name of the column.

oSortOrder :: Lens' Order Natural Source #

Indicates that the column is sorted in ascending order (== 1 ), or in descending order (==0 ).

Partition

data Partition Source #

Represents a slice of table data.

See: partition smart constructor.

Instances

Eq Partition Source # 
Data Partition Source # 

Methods

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

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

toConstr :: Partition -> Constr #

dataTypeOf :: Partition -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Partition Source # 
Show Partition Source # 
Generic Partition Source # 

Associated Types

type Rep Partition :: * -> * #

Hashable Partition Source # 
FromJSON Partition Source # 
NFData Partition Source # 

Methods

rnf :: Partition -> () #

type Rep Partition Source # 

partition :: Partition Source #

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

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

  • pCreationTime - The time at which the partition was created.
  • pValues - The values of the partition.
  • pLastAnalyzedTime - The last time at which column statistics were computed for this partition.
  • pStorageDescriptor - Provides information about the physical location where the partition is stored.
  • pDatabaseName - The name of the catalog database where the table in question is located.
  • pParameters - Partition parameters, in the form of a list of key-value pairs.
  • pLastAccessTime - The last time at which the partition was accessed.
  • pTableName - The name of the table in question.

pCreationTime :: Lens' Partition (Maybe UTCTime) Source #

The time at which the partition was created.

pValues :: Lens' Partition [Text] Source #

The values of the partition.

pLastAnalyzedTime :: Lens' Partition (Maybe UTCTime) Source #

The last time at which column statistics were computed for this partition.

pStorageDescriptor :: Lens' Partition (Maybe StorageDescriptor) Source #

Provides information about the physical location where the partition is stored.

pDatabaseName :: Lens' Partition (Maybe Text) Source #

The name of the catalog database where the table in question is located.

pParameters :: Lens' Partition (HashMap Text Text) Source #

Partition parameters, in the form of a list of key-value pairs.

pLastAccessTime :: Lens' Partition (Maybe UTCTime) Source #

The last time at which the partition was accessed.

pTableName :: Lens' Partition (Maybe Text) Source #

The name of the table in question.

PartitionError

data PartitionError Source #

Contains information about a partition error.

See: partitionError smart constructor.

Instances

Eq PartitionError Source # 
Data PartitionError Source # 

Methods

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

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

toConstr :: PartitionError -> Constr #

dataTypeOf :: PartitionError -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PartitionError Source # 
Show PartitionError Source # 
Generic PartitionError Source # 

Associated Types

type Rep PartitionError :: * -> * #

Hashable PartitionError Source # 
FromJSON PartitionError Source # 
NFData PartitionError Source # 

Methods

rnf :: PartitionError -> () #

type Rep PartitionError Source # 
type Rep PartitionError = D1 * (MetaData "PartitionError" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "PartitionError'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pePartitionValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_peErrorDetail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ErrorDetail)))))

partitionError :: PartitionError Source #

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

Use one of the following lenses to modify other fields as desired:

pePartitionValues :: Lens' PartitionError [Text] Source #

The values that define the partition.

peErrorDetail :: Lens' PartitionError (Maybe ErrorDetail) Source #

Details about the partition error.

PartitionInput

data PartitionInput Source #

The structure used to create and update a partion.

See: partitionInput smart constructor.

Instances

Eq PartitionInput Source # 
Data PartitionInput Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PartitionInput -> c PartitionInput #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PartitionInput #

toConstr :: PartitionInput -> Constr #

dataTypeOf :: PartitionInput -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PartitionInput) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PartitionInput) #

gmapT :: (forall b. Data b => b -> b) -> PartitionInput -> PartitionInput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PartitionInput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PartitionInput -> r #

gmapQ :: (forall d. Data d => d -> u) -> PartitionInput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PartitionInput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PartitionInput -> m PartitionInput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PartitionInput -> m PartitionInput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PartitionInput -> m PartitionInput #

Read PartitionInput Source # 
Show PartitionInput Source # 
Generic PartitionInput Source # 

Associated Types

type Rep PartitionInput :: * -> * #

Hashable PartitionInput Source # 
ToJSON PartitionInput Source # 
NFData PartitionInput Source # 

Methods

rnf :: PartitionInput -> () #

type Rep PartitionInput Source # 
type Rep PartitionInput = D1 * (MetaData "PartitionInput" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "PartitionInput'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_piValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_piLastAnalyzedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_piStorageDescriptor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StorageDescriptor))) ((:*:) * (S1 * (MetaSel (Just Symbol "_piParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) (S1 * (MetaSel (Just Symbol "_piLastAccessTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))))

partitionInput :: PartitionInput Source #

Creates a value of PartitionInput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • piValues - The values of the partition.
  • piLastAnalyzedTime - The last time at which column statistics were computed for this partition.
  • piStorageDescriptor - Provides information about the physical location where the partition is stored.
  • piParameters - Partition parameters, in the form of a list of key-value pairs.
  • piLastAccessTime - The last time at which the partition was accessed.

piValues :: Lens' PartitionInput [Text] Source #

The values of the partition.

piLastAnalyzedTime :: Lens' PartitionInput (Maybe UTCTime) Source #

The last time at which column statistics were computed for this partition.

piStorageDescriptor :: Lens' PartitionInput (Maybe StorageDescriptor) Source #

Provides information about the physical location where the partition is stored.

piParameters :: Lens' PartitionInput (HashMap Text Text) Source #

Partition parameters, in the form of a list of key-value pairs.

piLastAccessTime :: Lens' PartitionInput (Maybe UTCTime) Source #

The last time at which the partition was accessed.

PartitionValueList

data PartitionValueList Source #

Contains a list of values defining partitions.

See: partitionValueList smart constructor.

Instances

Eq PartitionValueList Source # 
Data PartitionValueList Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PartitionValueList -> c PartitionValueList #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PartitionValueList #

toConstr :: PartitionValueList -> Constr #

dataTypeOf :: PartitionValueList -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PartitionValueList) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PartitionValueList) #

gmapT :: (forall b. Data b => b -> b) -> PartitionValueList -> PartitionValueList #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PartitionValueList -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PartitionValueList -> r #

gmapQ :: (forall d. Data d => d -> u) -> PartitionValueList -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PartitionValueList -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PartitionValueList -> m PartitionValueList #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PartitionValueList -> m PartitionValueList #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PartitionValueList -> m PartitionValueList #

Read PartitionValueList Source # 
Show PartitionValueList Source # 
Generic PartitionValueList Source # 
Hashable PartitionValueList Source # 
ToJSON PartitionValueList Source # 
FromJSON PartitionValueList Source # 
NFData PartitionValueList Source # 

Methods

rnf :: PartitionValueList -> () #

type Rep PartitionValueList Source # 
type Rep PartitionValueList = D1 * (MetaData "PartitionValueList" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" True) (C1 * (MetaCons "PartitionValueList'" PrefixI True) (S1 * (MetaSel (Just Symbol "_pvlValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Text])))

partitionValueList :: PartitionValueList Source #

Creates a value of PartitionValueList with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pvlValues :: Lens' PartitionValueList [Text] Source #

The list of values.

PhysicalConnectionRequirements

data PhysicalConnectionRequirements Source #

Specifies the physical requirements for a connection.

See: physicalConnectionRequirements smart constructor.

Instances

Eq PhysicalConnectionRequirements Source # 
Data PhysicalConnectionRequirements Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PhysicalConnectionRequirements -> c PhysicalConnectionRequirements #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PhysicalConnectionRequirements #

toConstr :: PhysicalConnectionRequirements -> Constr #

dataTypeOf :: PhysicalConnectionRequirements -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PhysicalConnectionRequirements) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PhysicalConnectionRequirements) #

gmapT :: (forall b. Data b => b -> b) -> PhysicalConnectionRequirements -> PhysicalConnectionRequirements #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PhysicalConnectionRequirements -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PhysicalConnectionRequirements -> r #

gmapQ :: (forall d. Data d => d -> u) -> PhysicalConnectionRequirements -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PhysicalConnectionRequirements -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PhysicalConnectionRequirements -> m PhysicalConnectionRequirements #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PhysicalConnectionRequirements -> m PhysicalConnectionRequirements #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PhysicalConnectionRequirements -> m PhysicalConnectionRequirements #

Read PhysicalConnectionRequirements Source # 
Show PhysicalConnectionRequirements Source # 
Generic PhysicalConnectionRequirements Source # 
Hashable PhysicalConnectionRequirements Source # 
ToJSON PhysicalConnectionRequirements Source # 
FromJSON PhysicalConnectionRequirements Source # 
NFData PhysicalConnectionRequirements Source # 
type Rep PhysicalConnectionRequirements Source # 
type Rep PhysicalConnectionRequirements = D1 * (MetaData "PhysicalConnectionRequirements" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "PhysicalConnectionRequirements'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pcrSecurityGroupIdList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_pcrSubnetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_pcrAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

physicalConnectionRequirements :: PhysicalConnectionRequirements Source #

Creates a value of PhysicalConnectionRequirements with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pcrSecurityGroupIdList :: Lens' PhysicalConnectionRequirements [Text] Source #

The security group ID list used by the connection.

pcrSubnetId :: Lens' PhysicalConnectionRequirements (Maybe Text) Source #

The subnet ID used by the connection.

pcrAvailabilityZone :: Lens' PhysicalConnectionRequirements (Maybe Text) Source #

The connection's availability zone. This field is deprecated and has no effect.

Predecessor

data Predecessor Source #

A job run that was used in the predicate of a conditional trigger that triggered this job run.

See: predecessor smart constructor.

Instances

Eq Predecessor Source # 
Data Predecessor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Predecessor -> c Predecessor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Predecessor #

toConstr :: Predecessor -> Constr #

dataTypeOf :: Predecessor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Predecessor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Predecessor) #

gmapT :: (forall b. Data b => b -> b) -> Predecessor -> Predecessor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Predecessor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Predecessor -> r #

gmapQ :: (forall d. Data d => d -> u) -> Predecessor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Predecessor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Predecessor -> m Predecessor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Predecessor -> m Predecessor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Predecessor -> m Predecessor #

Read Predecessor Source # 
Show Predecessor Source # 
Generic Predecessor Source # 

Associated Types

type Rep Predecessor :: * -> * #

Hashable Predecessor Source # 
FromJSON Predecessor Source # 
NFData Predecessor Source # 

Methods

rnf :: Predecessor -> () #

type Rep Predecessor Source # 
type Rep Predecessor = D1 * (MetaData "Predecessor" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Predecessor'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pJobName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_pRunId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

predecessor :: Predecessor Source #

Creates a value of Predecessor with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • pJobName - The name of the job definition used by the predecessor job run.
  • pRunId - The job-run ID of the predecessor job run.

pJobName :: Lens' Predecessor (Maybe Text) Source #

The name of the job definition used by the predecessor job run.

pRunId :: Lens' Predecessor (Maybe Text) Source #

The job-run ID of the predecessor job run.

Predicate

data Predicate Source #

Defines the predicate of the trigger, which determines when it fires.

See: predicate smart constructor.

Instances

Eq Predicate Source # 
Data Predicate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Predicate -> c Predicate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Predicate #

toConstr :: Predicate -> Constr #

dataTypeOf :: Predicate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Predicate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Predicate) #

gmapT :: (forall b. Data b => b -> b) -> Predicate -> Predicate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Predicate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Predicate -> r #

gmapQ :: (forall d. Data d => d -> u) -> Predicate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Predicate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Predicate -> m Predicate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Predicate -> m Predicate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Predicate -> m Predicate #

Read Predicate Source # 
Show Predicate Source # 
Generic Predicate Source # 

Associated Types

type Rep Predicate :: * -> * #

Hashable Predicate Source # 
ToJSON Predicate Source # 
FromJSON Predicate Source # 
NFData Predicate Source # 

Methods

rnf :: Predicate -> () #

type Rep Predicate Source # 
type Rep Predicate = D1 * (MetaData "Predicate" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Predicate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pLogical") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Logical))) (S1 * (MetaSel (Just Symbol "_pConditions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Condition])))))

predicate :: Predicate Source #

Creates a value of Predicate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • pLogical - Optional field if only one condition is listed. If multiple conditions are listed, then this field is required.
  • pConditions - A list of the conditions that determine when the trigger will fire.

pLogical :: Lens' Predicate (Maybe Logical) Source #

Optional field if only one condition is listed. If multiple conditions are listed, then this field is required.

pConditions :: Lens' Predicate [Condition] Source #

A list of the conditions that determine when the trigger will fire.

ResourceURI

data ResourceURI Source #

URIs for function resources.

See: resourceURI smart constructor.

Instances

Eq ResourceURI Source # 
Data ResourceURI Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceURI -> c ResourceURI #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceURI #

toConstr :: ResourceURI -> Constr #

dataTypeOf :: ResourceURI -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceURI) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceURI) #

gmapT :: (forall b. Data b => b -> b) -> ResourceURI -> ResourceURI #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceURI -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceURI -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceURI -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceURI -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceURI -> m ResourceURI #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceURI -> m ResourceURI #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceURI -> m ResourceURI #

Read ResourceURI Source # 
Show ResourceURI Source # 
Generic ResourceURI Source # 

Associated Types

type Rep ResourceURI :: * -> * #

Hashable ResourceURI Source # 
ToJSON ResourceURI Source # 
FromJSON ResourceURI Source # 
NFData ResourceURI Source # 

Methods

rnf :: ResourceURI -> () #

type Rep ResourceURI Source # 
type Rep ResourceURI = D1 * (MetaData "ResourceURI" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "ResourceURI'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ruResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceType))) (S1 * (MetaSel (Just Symbol "_ruURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

resourceURI :: ResourceURI Source #

Creates a value of ResourceURI with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ruResourceType :: Lens' ResourceURI (Maybe ResourceType) Source #

The type of the resource.

ruURI :: Lens' ResourceURI (Maybe Text) Source #

The URI for accessing the resource.

S3Target

data S3Target Source #

Specifies a data store in Amazon S3.

See: s3Target smart constructor.

Instances

Eq S3Target Source # 
Data S3Target Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> S3Target -> c S3Target #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c S3Target #

toConstr :: S3Target -> Constr #

dataTypeOf :: S3Target -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c S3Target) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c S3Target) #

gmapT :: (forall b. Data b => b -> b) -> S3Target -> S3Target #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> S3Target -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> S3Target -> r #

gmapQ :: (forall d. Data d => d -> u) -> S3Target -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> S3Target -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> S3Target -> m S3Target #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> S3Target -> m S3Target #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> S3Target -> m S3Target #

Read S3Target Source # 
Show S3Target Source # 
Generic S3Target Source # 

Associated Types

type Rep S3Target :: * -> * #

Methods

from :: S3Target -> Rep S3Target x #

to :: Rep S3Target x -> S3Target #

Hashable S3Target Source # 

Methods

hashWithSalt :: Int -> S3Target -> Int #

hash :: S3Target -> Int #

ToJSON S3Target Source # 
FromJSON S3Target Source # 
NFData S3Target Source # 

Methods

rnf :: S3Target -> () #

type Rep S3Target Source # 
type Rep S3Target = D1 * (MetaData "S3Target" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "S3Target'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_stPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_stExclusions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))))

s3Target :: S3Target Source #

Creates a value of S3Target with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

stPath :: Lens' S3Target (Maybe Text) Source #

The path to the Amazon S3 target.

stExclusions :: Lens' S3Target [Text] Source #

A list of glob patterns used to exclude from the crawl. For more information, see Catalog Tables with a Crawler .

Schedule

data Schedule Source #

A scheduling object using a cron statement to schedule an event.

See: schedule smart constructor.

Instances

Eq Schedule Source # 
Data Schedule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Schedule -> c Schedule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Schedule #

toConstr :: Schedule -> Constr #

dataTypeOf :: Schedule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Schedule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schedule) #

gmapT :: (forall b. Data b => b -> b) -> Schedule -> Schedule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schedule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schedule -> r #

gmapQ :: (forall d. Data d => d -> u) -> Schedule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Schedule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Schedule -> m Schedule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Schedule -> m Schedule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Schedule -> m Schedule #

Read Schedule Source # 
Show Schedule Source # 
Generic Schedule Source # 

Associated Types

type Rep Schedule :: * -> * #

Methods

from :: Schedule -> Rep Schedule x #

to :: Rep Schedule x -> Schedule #

Hashable Schedule Source # 

Methods

hashWithSalt :: Int -> Schedule -> Int #

hash :: Schedule -> Int #

FromJSON Schedule Source # 
NFData Schedule Source # 

Methods

rnf :: Schedule -> () #

type Rep Schedule Source # 
type Rep Schedule = D1 * (MetaData "Schedule" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Schedule'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ScheduleState))) (S1 * (MetaSel (Just Symbol "_sScheduleExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

schedule :: Schedule Source #

Creates a value of Schedule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sState :: Lens' Schedule (Maybe ScheduleState) Source #

The state of the schedule.

sScheduleExpression :: Lens' Schedule (Maybe Text) Source #

A cron expression used to specify the schedule (see Time-Based Schedules for Jobs and Crawlers . For example, to run something every day at 12:15 UTC, you would specify: cron(15 12 * * ? *) .

SchemaChangePolicy

data SchemaChangePolicy Source #

Crawler policy for update and deletion behavior.

See: schemaChangePolicy smart constructor.

Instances

Eq SchemaChangePolicy Source # 
Data SchemaChangePolicy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SchemaChangePolicy -> c SchemaChangePolicy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SchemaChangePolicy #

toConstr :: SchemaChangePolicy -> Constr #

dataTypeOf :: SchemaChangePolicy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SchemaChangePolicy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaChangePolicy) #

gmapT :: (forall b. Data b => b -> b) -> SchemaChangePolicy -> SchemaChangePolicy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SchemaChangePolicy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SchemaChangePolicy -> r #

gmapQ :: (forall d. Data d => d -> u) -> SchemaChangePolicy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemaChangePolicy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SchemaChangePolicy -> m SchemaChangePolicy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemaChangePolicy -> m SchemaChangePolicy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemaChangePolicy -> m SchemaChangePolicy #

Read SchemaChangePolicy Source # 
Show SchemaChangePolicy Source # 
Generic SchemaChangePolicy Source # 
Hashable SchemaChangePolicy Source # 
ToJSON SchemaChangePolicy Source # 
FromJSON SchemaChangePolicy Source # 
NFData SchemaChangePolicy Source # 

Methods

rnf :: SchemaChangePolicy -> () #

type Rep SchemaChangePolicy Source # 
type Rep SchemaChangePolicy = D1 * (MetaData "SchemaChangePolicy" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "SchemaChangePolicy'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_scpDeleteBehavior") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DeleteBehavior))) (S1 * (MetaSel (Just Symbol "_scpUpdateBehavior") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe UpdateBehavior)))))

schemaChangePolicy :: SchemaChangePolicy Source #

Creates a value of SchemaChangePolicy with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

scpDeleteBehavior :: Lens' SchemaChangePolicy (Maybe DeleteBehavior) Source #

The deletion behavior when the crawler finds a deleted object.

scpUpdateBehavior :: Lens' SchemaChangePolicy (Maybe UpdateBehavior) Source #

The update behavior when the crawler finds a changed schema.

Segment

data Segment Source #

Defines a non-overlapping region of a table's partitions, allowing multiple requests to be executed in parallel.

See: segment smart constructor.

Instances

Eq Segment Source # 

Methods

(==) :: Segment -> Segment -> Bool #

(/=) :: Segment -> Segment -> Bool #

Data Segment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Segment -> c Segment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Segment #

toConstr :: Segment -> Constr #

dataTypeOf :: Segment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Segment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Segment) #

gmapT :: (forall b. Data b => b -> b) -> Segment -> Segment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Segment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Segment -> r #

gmapQ :: (forall d. Data d => d -> u) -> Segment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Segment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

Read Segment Source # 
Show Segment Source # 
Generic Segment Source # 

Associated Types

type Rep Segment :: * -> * #

Methods

from :: Segment -> Rep Segment x #

to :: Rep Segment x -> Segment #

Hashable Segment Source # 

Methods

hashWithSalt :: Int -> Segment -> Int #

hash :: Segment -> Int #

ToJSON Segment Source # 
NFData Segment Source # 

Methods

rnf :: Segment -> () #

type Rep Segment Source # 
type Rep Segment = D1 * (MetaData "Segment" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Segment'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sSegmentNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat)) (S1 * (MetaSel (Just Symbol "_sTotalSegments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat))))

segment Source #

Creates a value of Segment with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sSegmentNumber - The zero-based index number of the this segment. For example, if the total number of segments is 4, SegmentNumber values will range from zero through three.
  • sTotalSegments - The total numer of segments.

sSegmentNumber :: Lens' Segment Natural Source #

The zero-based index number of the this segment. For example, if the total number of segments is 4, SegmentNumber values will range from zero through three.

sTotalSegments :: Lens' Segment Natural Source #

The total numer of segments.

SerDeInfo

data SerDeInfo Source #

Information about a serialization/deserialization program (SerDe) which serves as an extractor and loader.

See: serDeInfo smart constructor.

Instances

Eq SerDeInfo Source # 
Data SerDeInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SerDeInfo -> c SerDeInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SerDeInfo #

toConstr :: SerDeInfo -> Constr #

dataTypeOf :: SerDeInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SerDeInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SerDeInfo) #

gmapT :: (forall b. Data b => b -> b) -> SerDeInfo -> SerDeInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SerDeInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SerDeInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> SerDeInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SerDeInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SerDeInfo -> m SerDeInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SerDeInfo -> m SerDeInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SerDeInfo -> m SerDeInfo #

Read SerDeInfo Source # 
Show SerDeInfo Source # 
Generic SerDeInfo Source # 

Associated Types

type Rep SerDeInfo :: * -> * #

Hashable SerDeInfo Source # 
ToJSON SerDeInfo Source # 
FromJSON SerDeInfo Source # 
NFData SerDeInfo Source # 

Methods

rnf :: SerDeInfo -> () #

type Rep SerDeInfo Source # 
type Rep SerDeInfo = D1 * (MetaData "SerDeInfo" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "SerDeInfo'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdiSerializationLibrary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_sdiParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))))))

serDeInfo :: SerDeInfo Source #

Creates a value of SerDeInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sdiSerializationLibrary - Usually the class that implements the SerDe. An example is: org.apache.hadoop.hive.serde2.columnar.ColumnarSerDe .
  • sdiName - Name of the SerDe.
  • sdiParameters - A list of initialization parameters for the SerDe, in key-value form.

sdiSerializationLibrary :: Lens' SerDeInfo (Maybe Text) Source #

Usually the class that implements the SerDe. An example is: org.apache.hadoop.hive.serde2.columnar.ColumnarSerDe .

sdiName :: Lens' SerDeInfo (Maybe Text) Source #

Name of the SerDe.

sdiParameters :: Lens' SerDeInfo (HashMap Text Text) Source #

A list of initialization parameters for the SerDe, in key-value form.

SkewedInfo

data SkewedInfo Source #

Specifies skewed values in a table. Skewed are ones that occur with very high frequency.

See: skewedInfo smart constructor.

Instances

Eq SkewedInfo Source # 
Data SkewedInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SkewedInfo -> c SkewedInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SkewedInfo #

toConstr :: SkewedInfo -> Constr #

dataTypeOf :: SkewedInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SkewedInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SkewedInfo) #

gmapT :: (forall b. Data b => b -> b) -> SkewedInfo -> SkewedInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SkewedInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SkewedInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> SkewedInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SkewedInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SkewedInfo -> m SkewedInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SkewedInfo -> m SkewedInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SkewedInfo -> m SkewedInfo #

Read SkewedInfo Source # 
Show SkewedInfo Source # 
Generic SkewedInfo Source # 

Associated Types

type Rep SkewedInfo :: * -> * #

Hashable SkewedInfo Source # 
ToJSON SkewedInfo Source # 
FromJSON SkewedInfo Source # 
NFData SkewedInfo Source # 

Methods

rnf :: SkewedInfo -> () #

type Rep SkewedInfo Source # 
type Rep SkewedInfo = D1 * (MetaData "SkewedInfo" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "SkewedInfo'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_siSkewedColumnValueLocationMaps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_siSkewedColumnValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_siSkewedColumnNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))))))

skewedInfo :: SkewedInfo Source #

Creates a value of SkewedInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

siSkewedColumnValueLocationMaps :: Lens' SkewedInfo (HashMap Text Text) Source #

A mapping of skewed values to the columns that contain them.

siSkewedColumnValues :: Lens' SkewedInfo [Text] Source #

A list of values that appear so frequently as to be considered skewed.

siSkewedColumnNames :: Lens' SkewedInfo [Text] Source #

A list of names of columns that contain skewed values.

StorageDescriptor

data StorageDescriptor Source #

Describes the physical storage of table data.

See: storageDescriptor smart constructor.

Instances

Eq StorageDescriptor Source # 
Data StorageDescriptor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StorageDescriptor -> c StorageDescriptor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StorageDescriptor #

toConstr :: StorageDescriptor -> Constr #

dataTypeOf :: StorageDescriptor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StorageDescriptor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StorageDescriptor) #

gmapT :: (forall b. Data b => b -> b) -> StorageDescriptor -> StorageDescriptor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StorageDescriptor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StorageDescriptor -> r #

gmapQ :: (forall d. Data d => d -> u) -> StorageDescriptor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StorageDescriptor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StorageDescriptor -> m StorageDescriptor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageDescriptor -> m StorageDescriptor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageDescriptor -> m StorageDescriptor #

Read StorageDescriptor Source # 
Show StorageDescriptor Source # 
Generic StorageDescriptor Source # 
Hashable StorageDescriptor Source # 
ToJSON StorageDescriptor Source # 
FromJSON StorageDescriptor Source # 
NFData StorageDescriptor Source # 

Methods

rnf :: StorageDescriptor -> () #

type Rep StorageDescriptor Source # 
type Rep StorageDescriptor = D1 * (MetaData "StorageDescriptor" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "StorageDescriptor'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_sdSortColumns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Order]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdCompressed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_sdLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdBucketColumns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdSerdeInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SerDeInfo))) (S1 * (MetaSel (Just Symbol "_sdOutputFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_sdNumberOfBuckets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdStoredAsSubDirectories") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_sdParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdInputFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sdSkewedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SkewedInfo))) (S1 * (MetaSel (Just Symbol "_sdColumns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Column]))))))))

storageDescriptor :: StorageDescriptor Source #

Creates a value of StorageDescriptor with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sdSortColumns - A list specifying the sort order of each bucket in the table.
  • sdCompressed - True if the data in the table is compressed, or False if not.
  • sdLocation - The physical location of the table. By default this takes the form of the warehouse location, followed by the database location in the warehouse, followed by the table name.
  • sdBucketColumns - A list of reducer grouping columns, clustering columns, and bucketing columns in the table.
  • sdSerdeInfo - Serialization/deserialization (SerDe) information.
  • sdOutputFormat - The output format: SequenceFileOutputFormat (binary), or IgnoreKeyTextOutputFormat , or a custom format.
  • sdNumberOfBuckets - Must be specified if the table contains any dimension columns.
  • sdStoredAsSubDirectories - True if the table data is stored in subdirectories, or False if not.
  • sdParameters - User-supplied properties in key-value form.
  • sdInputFormat - The input format: SequenceFileInputFormat (binary), or TextInputFormat , or a custom format.
  • sdSkewedInfo - Information about values that appear very frequently in a column (skewed values).
  • sdColumns - A list of the Columns in the table.

sdSortColumns :: Lens' StorageDescriptor [Order] Source #

A list specifying the sort order of each bucket in the table.

sdCompressed :: Lens' StorageDescriptor (Maybe Bool) Source #

True if the data in the table is compressed, or False if not.

sdLocation :: Lens' StorageDescriptor (Maybe Text) Source #

The physical location of the table. By default this takes the form of the warehouse location, followed by the database location in the warehouse, followed by the table name.

sdBucketColumns :: Lens' StorageDescriptor [Text] Source #

A list of reducer grouping columns, clustering columns, and bucketing columns in the table.

sdSerdeInfo :: Lens' StorageDescriptor (Maybe SerDeInfo) Source #

Serialization/deserialization (SerDe) information.

sdOutputFormat :: Lens' StorageDescriptor (Maybe Text) Source #

The output format: SequenceFileOutputFormat (binary), or IgnoreKeyTextOutputFormat , or a custom format.

sdNumberOfBuckets :: Lens' StorageDescriptor (Maybe Int) Source #

Must be specified if the table contains any dimension columns.

sdStoredAsSubDirectories :: Lens' StorageDescriptor (Maybe Bool) Source #

True if the table data is stored in subdirectories, or False if not.

sdParameters :: Lens' StorageDescriptor (HashMap Text Text) Source #

User-supplied properties in key-value form.

sdInputFormat :: Lens' StorageDescriptor (Maybe Text) Source #

The input format: SequenceFileInputFormat (binary), or TextInputFormat , or a custom format.

sdSkewedInfo :: Lens' StorageDescriptor (Maybe SkewedInfo) Source #

Information about values that appear very frequently in a column (skewed values).

sdColumns :: Lens' StorageDescriptor [Column] Source #

A list of the Columns in the table.

Table

data Table Source #

Represents a collection of related data organized in columns and rows.

See: table smart constructor.

Instances

Eq Table Source # 

Methods

(==) :: Table -> Table -> Bool #

(/=) :: Table -> Table -> Bool #

Data Table Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Table -> c Table #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Table #

toConstr :: Table -> Constr #

dataTypeOf :: Table -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Table) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Table) #

gmapT :: (forall b. Data b => b -> b) -> Table -> Table #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r #

gmapQ :: (forall d. Data d => d -> u) -> Table -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Table -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Table -> m Table #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Table -> m Table #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Table -> m Table #

Read Table Source # 
Show Table Source # 

Methods

showsPrec :: Int -> Table -> ShowS #

show :: Table -> String #

showList :: [Table] -> ShowS #

Generic Table Source # 

Associated Types

type Rep Table :: * -> * #

Methods

from :: Table -> Rep Table x #

to :: Rep Table x -> Table #

Hashable Table Source # 

Methods

hashWithSalt :: Int -> Table -> Int #

hash :: Table -> Int #

FromJSON Table Source # 
NFData Table Source # 

Methods

rnf :: Table -> () #

type Rep Table Source # 
type Rep Table = D1 * (MetaData "Table" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "Table'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tRetention") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_tCreatedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tTableType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tViewOriginalText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tViewExpandedText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tLastAnalyzedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tStorageDescriptor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StorageDescriptor))) (S1 * (MetaSel (Just Symbol "_tDatabaseName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) (S1 * (MetaSel (Just Symbol "_tLastAccessTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tPartitionKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Column])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_tName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))))

table Source #

Arguments

:: Text

tName

-> Table 

Creates a value of Table with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tRetention - Retention time for this table.
  • tCreatedBy - Person or entity who created the table.
  • tTableType - The type of this table (EXTERNAL_TABLE , VIRTUAL_VIEW , etc.).
  • tOwner - Owner of the table.
  • tViewOriginalText - If the table is a view, the original text of the view; otherwise null .
  • tUpdateTime - Last time the table was updated.
  • tViewExpandedText - If the table is a view, the expanded text of the view; otherwise null .
  • tLastAnalyzedTime - Last time column statistics were computed for this table.
  • tStorageDescriptor - A storage descriptor containing information about the physical storage of this table.
  • tDatabaseName - Name of the metadata database where the table metadata resides. For Hive compatibility, this must be all lowercase.
  • tParameters - Properties associated with this table, as a list of key-value pairs.
  • tLastAccessTime - Last time the table was accessed. This is usually taken from HDFS, and may not be reliable.
  • tDescription - Description of the table.
  • tPartitionKeys - A list of columns by which the table is partitioned. Only primitive types are supported as partition keys.
  • tCreateTime - Time when the table definition was created in the Data Catalog.
  • tName - Name of the table. For Hive compatibility, this must be entirely lowercase.

tRetention :: Lens' Table (Maybe Natural) Source #

Retention time for this table.

tCreatedBy :: Lens' Table (Maybe Text) Source #

Person or entity who created the table.

tTableType :: Lens' Table (Maybe Text) Source #

The type of this table (EXTERNAL_TABLE , VIRTUAL_VIEW , etc.).

tOwner :: Lens' Table (Maybe Text) Source #

Owner of the table.

tViewOriginalText :: Lens' Table (Maybe Text) Source #

If the table is a view, the original text of the view; otherwise null .

tUpdateTime :: Lens' Table (Maybe UTCTime) Source #

Last time the table was updated.

tViewExpandedText :: Lens' Table (Maybe Text) Source #

If the table is a view, the expanded text of the view; otherwise null .

tLastAnalyzedTime :: Lens' Table (Maybe UTCTime) Source #

Last time column statistics were computed for this table.

tStorageDescriptor :: Lens' Table (Maybe StorageDescriptor) Source #

A storage descriptor containing information about the physical storage of this table.

tDatabaseName :: Lens' Table (Maybe Text) Source #

Name of the metadata database where the table metadata resides. For Hive compatibility, this must be all lowercase.

tParameters :: Lens' Table (HashMap Text Text) Source #

Properties associated with this table, as a list of key-value pairs.

tLastAccessTime :: Lens' Table (Maybe UTCTime) Source #

Last time the table was accessed. This is usually taken from HDFS, and may not be reliable.

tDescription :: Lens' Table (Maybe Text) Source #

Description of the table.

tPartitionKeys :: Lens' Table [Column] Source #

A list of columns by which the table is partitioned. Only primitive types are supported as partition keys.

tCreateTime :: Lens' Table (Maybe UTCTime) Source #

Time when the table definition was created in the Data Catalog.

tName :: Lens' Table Text Source #

Name of the table. For Hive compatibility, this must be entirely lowercase.

TableError

data TableError Source #

An error record for table operations.

See: tableError smart constructor.

Instances

Eq TableError Source # 
Data TableError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableError -> c TableError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableError #

toConstr :: TableError -> Constr #

dataTypeOf :: TableError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableError) #

gmapT :: (forall b. Data b => b -> b) -> TableError -> TableError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableError -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableError -> m TableError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableError -> m TableError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableError -> m TableError #

Read TableError Source # 
Show TableError Source # 
Generic TableError Source # 

Associated Types

type Rep TableError :: * -> * #

Hashable TableError Source # 
FromJSON TableError Source # 
NFData TableError Source # 

Methods

rnf :: TableError -> () #

type Rep TableError Source # 
type Rep TableError = D1 * (MetaData "TableError" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "TableError'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_teTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_teErrorDetail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ErrorDetail)))))

tableError :: TableError Source #

Creates a value of TableError with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • teTableName - Name of the table. For Hive compatibility, this must be entirely lowercase.
  • teErrorDetail - Detail about the error.

teTableName :: Lens' TableError (Maybe Text) Source #

Name of the table. For Hive compatibility, this must be entirely lowercase.

teErrorDetail :: Lens' TableError (Maybe ErrorDetail) Source #

Detail about the error.

TableInput

data TableInput Source #

Structure used to create or update the table.

See: tableInput smart constructor.

Instances

Eq TableInput Source # 
Data TableInput Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableInput -> c TableInput #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableInput #

toConstr :: TableInput -> Constr #

dataTypeOf :: TableInput -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableInput) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableInput) #

gmapT :: (forall b. Data b => b -> b) -> TableInput -> TableInput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableInput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableInput -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableInput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableInput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableInput -> m TableInput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableInput -> m TableInput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableInput -> m TableInput #

Read TableInput Source # 
Show TableInput Source # 
Generic TableInput Source # 

Associated Types

type Rep TableInput :: * -> * #

Hashable TableInput Source # 
ToJSON TableInput Source # 
NFData TableInput Source # 

Methods

rnf :: TableInput -> () #

type Rep TableInput Source # 
type Rep TableInput = D1 * (MetaData "TableInput" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "TableInput'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tiRetention") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tiTableType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tiOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tiViewOriginalText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tiViewExpandedText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tiLastAnalyzedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tiStorageDescriptor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StorageDescriptor))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tiParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) (S1 * (MetaSel (Just Symbol "_tiLastAccessTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tiDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tiPartitionKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Column]))) (S1 * (MetaSel (Just Symbol "_tiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))))

tableInput Source #

Arguments

:: Text

tiName

-> TableInput 

Creates a value of TableInput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tiRetention - Retention time for this table.
  • tiTableType - The type of this table (EXTERNAL_TABLE , VIRTUAL_VIEW , etc.).
  • tiOwner - Owner of the table.
  • tiViewOriginalText - If the table is a view, the original text of the view; otherwise null .
  • tiViewExpandedText - If the table is a view, the expanded text of the view; otherwise null .
  • tiLastAnalyzedTime - Last time column statistics were computed for this table.
  • tiStorageDescriptor - A storage descriptor containing information about the physical storage of this table.
  • tiParameters - Properties associated with this table, as a list of key-value pairs.
  • tiLastAccessTime - Last time the table was accessed.
  • tiDescription - Description of the table.
  • tiPartitionKeys - A list of columns by which the table is partitioned. Only primitive types are supported as partition keys.
  • tiName - Name of the table. For Hive compatibility, this is folded to lowercase when it is stored.

tiRetention :: Lens' TableInput (Maybe Natural) Source #

Retention time for this table.

tiTableType :: Lens' TableInput (Maybe Text) Source #

The type of this table (EXTERNAL_TABLE , VIRTUAL_VIEW , etc.).

tiOwner :: Lens' TableInput (Maybe Text) Source #

Owner of the table.

tiViewOriginalText :: Lens' TableInput (Maybe Text) Source #

If the table is a view, the original text of the view; otherwise null .

tiViewExpandedText :: Lens' TableInput (Maybe Text) Source #

If the table is a view, the expanded text of the view; otherwise null .

tiLastAnalyzedTime :: Lens' TableInput (Maybe UTCTime) Source #

Last time column statistics were computed for this table.

tiStorageDescriptor :: Lens' TableInput (Maybe StorageDescriptor) Source #

A storage descriptor containing information about the physical storage of this table.

tiParameters :: Lens' TableInput (HashMap Text Text) Source #

Properties associated with this table, as a list of key-value pairs.

tiLastAccessTime :: Lens' TableInput (Maybe UTCTime) Source #

Last time the table was accessed.

tiDescription :: Lens' TableInput (Maybe Text) Source #

Description of the table.

tiPartitionKeys :: Lens' TableInput [Column] Source #

A list of columns by which the table is partitioned. Only primitive types are supported as partition keys.

tiName :: Lens' TableInput Text Source #

Name of the table. For Hive compatibility, this is folded to lowercase when it is stored.

TableVersion

data TableVersion Source #

Specifies a version of a table.

See: tableVersion smart constructor.

Instances

Eq TableVersion Source # 
Data TableVersion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableVersion -> c TableVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableVersion #

toConstr :: TableVersion -> Constr #

dataTypeOf :: TableVersion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableVersion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableVersion) #

gmapT :: (forall b. Data b => b -> b) -> TableVersion -> TableVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableVersion -> m TableVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableVersion -> m TableVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableVersion -> m TableVersion #

Read TableVersion Source # 
Show TableVersion Source # 
Generic TableVersion Source # 

Associated Types

type Rep TableVersion :: * -> * #

Hashable TableVersion Source # 
FromJSON TableVersion Source # 
NFData TableVersion Source # 

Methods

rnf :: TableVersion -> () #

type Rep TableVersion Source # 
type Rep TableVersion = D1 * (MetaData "TableVersion" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "TableVersion'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tvVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tvTable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Table)))))

tableVersion :: TableVersion Source #

Creates a value of TableVersion with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tvVersionId - The ID value that identifies this table version.
  • tvTable - The table in question

tvVersionId :: Lens' TableVersion (Maybe Text) Source #

The ID value that identifies this table version.

tvTable :: Lens' TableVersion (Maybe Table) Source #

The table in question

TableVersionError

data TableVersionError Source #

An error record for table-version operations.

See: tableVersionError smart constructor.

Instances

Eq TableVersionError Source # 
Data TableVersionError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableVersionError -> c TableVersionError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableVersionError #

toConstr :: TableVersionError -> Constr #

dataTypeOf :: TableVersionError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableVersionError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableVersionError) #

gmapT :: (forall b. Data b => b -> b) -> TableVersionError -> TableVersionError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableVersionError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableVersionError -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableVersionError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableVersionError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableVersionError -> m TableVersionError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableVersionError -> m TableVersionError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableVersionError -> m TableVersionError #

Read TableVersionError Source # 
Show TableVersionError Source # 
Generic TableVersionError Source # 
Hashable TableVersionError Source # 
FromJSON TableVersionError Source # 
NFData TableVersionError Source # 

Methods

rnf :: TableVersionError -> () #

type Rep TableVersionError Source # 
type Rep TableVersionError = D1 * (MetaData "TableVersionError" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "TableVersionError'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tveVersionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tveTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tveErrorDetail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ErrorDetail))))))

tableVersionError :: TableVersionError Source #

Creates a value of TableVersionError with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tveVersionId :: Lens' TableVersionError (Maybe Text) Source #

The ID value of the version in question.

tveTableName :: Lens' TableVersionError (Maybe Text) Source #

The name of the table in question.

Trigger

data Trigger Source #

Information about a specific trigger.

See: trigger smart constructor.

Instances

Eq Trigger Source # 

Methods

(==) :: Trigger -> Trigger -> Bool #

(/=) :: Trigger -> Trigger -> Bool #

Data Trigger Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Trigger -> c Trigger #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Trigger #

toConstr :: Trigger -> Constr #

dataTypeOf :: Trigger -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Trigger) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Trigger) #

gmapT :: (forall b. Data b => b -> b) -> Trigger -> Trigger #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Trigger -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Trigger -> r #

gmapQ :: (forall d. Data d => d -> u) -> Trigger -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Trigger -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Trigger -> m Trigger #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Trigger -> m Trigger #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Trigger -> m Trigger #

Read Trigger Source # 
Show Trigger Source # 
Generic Trigger Source # 

Associated Types

type Rep Trigger :: * -> * #

Methods

from :: Trigger -> Rep Trigger x #

to :: Rep Trigger x -> Trigger #

Hashable Trigger Source # 

Methods

hashWithSalt :: Int -> Trigger -> Int #

hash :: Trigger -> Int #

FromJSON Trigger Source # 
NFData Trigger Source # 

Methods

rnf :: Trigger -> () #

type Rep Trigger Source # 

trigger :: Trigger Source #

Creates a value of Trigger with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

triState :: Lens' Trigger (Maybe TriggerState) Source #

The current state of the trigger.

triActions :: Lens' Trigger [Action] Source #

The actions initiated by this trigger.

triSchedule :: Lens' Trigger (Maybe Text) Source #

A cron expression used to specify the schedule (see Time-Based Schedules for Jobs and Crawlers . For example, to run something every day at 12:15 UTC, you would specify: cron(15 12 * * ? *) .

triPredicate :: Lens' Trigger (Maybe Predicate) Source #

The predicate of this trigger, which defines when it will fire.

triName :: Lens' Trigger (Maybe Text) Source #

Name of the trigger.

triId :: Lens' Trigger (Maybe Text) Source #

Reserved for future use.

triType :: Lens' Trigger (Maybe TriggerType) Source #

The type of trigger that this is.

triDescription :: Lens' Trigger (Maybe Text) Source #

A description of this trigger.

TriggerUpdate

data TriggerUpdate Source #

A structure used to provide information used to update a trigger. This object will update the the previous trigger definition by overwriting it completely.

See: triggerUpdate smart constructor.

Instances

Eq TriggerUpdate Source # 
Data TriggerUpdate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TriggerUpdate -> c TriggerUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TriggerUpdate #

toConstr :: TriggerUpdate -> Constr #

dataTypeOf :: TriggerUpdate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TriggerUpdate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TriggerUpdate) #

gmapT :: (forall b. Data b => b -> b) -> TriggerUpdate -> TriggerUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TriggerUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TriggerUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> TriggerUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TriggerUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TriggerUpdate -> m TriggerUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TriggerUpdate -> m TriggerUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TriggerUpdate -> m TriggerUpdate #

Read TriggerUpdate Source # 
Show TriggerUpdate Source # 
Generic TriggerUpdate Source # 

Associated Types

type Rep TriggerUpdate :: * -> * #

Hashable TriggerUpdate Source # 
ToJSON TriggerUpdate Source # 
NFData TriggerUpdate Source # 

Methods

rnf :: TriggerUpdate -> () #

type Rep TriggerUpdate Source # 
type Rep TriggerUpdate = D1 * (MetaData "TriggerUpdate" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "TriggerUpdate'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tuActions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Action]))) (S1 * (MetaSel (Just Symbol "_tuSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tuPredicate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Predicate))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tuName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tuDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

triggerUpdate :: TriggerUpdate Source #

Creates a value of TriggerUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tuActions :: Lens' TriggerUpdate [Action] Source #

The actions initiated by this trigger.

tuSchedule :: Lens' TriggerUpdate (Maybe Text) Source #

A cron expression used to specify the schedule (see Time-Based Schedules for Jobs and Crawlers . For example, to run something every day at 12:15 UTC, you would specify: cron(15 12 * * ? *) .

tuPredicate :: Lens' TriggerUpdate (Maybe Predicate) Source #

The predicate of this trigger, which defines when it will fire.

tuName :: Lens' TriggerUpdate (Maybe Text) Source #

Reserved for future use.

tuDescription :: Lens' TriggerUpdate (Maybe Text) Source #

A description of this trigger.

UpdateGrokClassifierRequest

data UpdateGrokClassifierRequest Source #

Specifies a grok classifier to update when passed to UpdateClassifier .

See: updateGrokClassifierRequest smart constructor.

Instances

Eq UpdateGrokClassifierRequest Source # 
Data UpdateGrokClassifierRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateGrokClassifierRequest -> c UpdateGrokClassifierRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateGrokClassifierRequest #

toConstr :: UpdateGrokClassifierRequest -> Constr #

dataTypeOf :: UpdateGrokClassifierRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateGrokClassifierRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateGrokClassifierRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateGrokClassifierRequest -> UpdateGrokClassifierRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateGrokClassifierRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateGrokClassifierRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateGrokClassifierRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateGrokClassifierRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateGrokClassifierRequest -> m UpdateGrokClassifierRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateGrokClassifierRequest -> m UpdateGrokClassifierRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateGrokClassifierRequest -> m UpdateGrokClassifierRequest #

Read UpdateGrokClassifierRequest Source # 
Show UpdateGrokClassifierRequest Source # 
Generic UpdateGrokClassifierRequest Source # 
Hashable UpdateGrokClassifierRequest Source # 
ToJSON UpdateGrokClassifierRequest Source # 
NFData UpdateGrokClassifierRequest Source # 
type Rep UpdateGrokClassifierRequest Source # 
type Rep UpdateGrokClassifierRequest = D1 * (MetaData "UpdateGrokClassifierRequest" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "UpdateGrokClassifierRequest'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ugcrClassification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ugcrCustomPatterns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ugcrGrokPattern") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ugcrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

updateGrokClassifierRequest Source #

Creates a value of UpdateGrokClassifierRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ugcrClassification - An identifier of the data format that the classifier matches, such as Twitter, JSON, Omniture logs, Amazon CloudWatch Logs, and so on.
  • ugcrCustomPatterns - Optional custom grok patterns used by this classifier.
  • ugcrGrokPattern - The grok pattern used by this classifier.
  • ugcrName - The name of the GrokClassifier .

ugcrClassification :: Lens' UpdateGrokClassifierRequest (Maybe Text) Source #

An identifier of the data format that the classifier matches, such as Twitter, JSON, Omniture logs, Amazon CloudWatch Logs, and so on.

ugcrCustomPatterns :: Lens' UpdateGrokClassifierRequest (Maybe Text) Source #

Optional custom grok patterns used by this classifier.

ugcrGrokPattern :: Lens' UpdateGrokClassifierRequest (Maybe Text) Source #

The grok pattern used by this classifier.

ugcrName :: Lens' UpdateGrokClassifierRequest Text Source #

The name of the GrokClassifier .

UpdateJSONClassifierRequest

data UpdateJSONClassifierRequest Source #

Specifies a JSON classifier to be updated.

See: updateJSONClassifierRequest smart constructor.

Instances

Eq UpdateJSONClassifierRequest Source # 
Data UpdateJSONClassifierRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateJSONClassifierRequest -> c UpdateJSONClassifierRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateJSONClassifierRequest #

toConstr :: UpdateJSONClassifierRequest -> Constr #

dataTypeOf :: UpdateJSONClassifierRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateJSONClassifierRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateJSONClassifierRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateJSONClassifierRequest -> UpdateJSONClassifierRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateJSONClassifierRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateJSONClassifierRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateJSONClassifierRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateJSONClassifierRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateJSONClassifierRequest -> m UpdateJSONClassifierRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateJSONClassifierRequest -> m UpdateJSONClassifierRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateJSONClassifierRequest -> m UpdateJSONClassifierRequest #

Read UpdateJSONClassifierRequest Source # 
Show UpdateJSONClassifierRequest Source # 
Generic UpdateJSONClassifierRequest Source # 
Hashable UpdateJSONClassifierRequest Source # 
ToJSON UpdateJSONClassifierRequest Source # 
NFData UpdateJSONClassifierRequest Source # 
type Rep UpdateJSONClassifierRequest Source # 
type Rep UpdateJSONClassifierRequest = D1 * (MetaData "UpdateJSONClassifierRequest" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "UpdateJSONClassifierRequest'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ujcrJSONPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ujcrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

updateJSONClassifierRequest Source #

Creates a value of UpdateJSONClassifierRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ujcrJSONPath :: Lens' UpdateJSONClassifierRequest (Maybe Text) Source #

A JsonPath string defining the JSON data for the classifier to classify. AWS Glue supports a subset of JsonPath, as described in Writing JsonPath Custom Classifiers .

ujcrName :: Lens' UpdateJSONClassifierRequest Text Source #

The name of the classifier.

UpdateXMLClassifierRequest

data UpdateXMLClassifierRequest Source #

Specifies an XML classifier to be updated.

See: updateXMLClassifierRequest smart constructor.

Instances

Eq UpdateXMLClassifierRequest Source # 
Data UpdateXMLClassifierRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateXMLClassifierRequest -> c UpdateXMLClassifierRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateXMLClassifierRequest #

toConstr :: UpdateXMLClassifierRequest -> Constr #

dataTypeOf :: UpdateXMLClassifierRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateXMLClassifierRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateXMLClassifierRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateXMLClassifierRequest -> UpdateXMLClassifierRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateXMLClassifierRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateXMLClassifierRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateXMLClassifierRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateXMLClassifierRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateXMLClassifierRequest -> m UpdateXMLClassifierRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateXMLClassifierRequest -> m UpdateXMLClassifierRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateXMLClassifierRequest -> m UpdateXMLClassifierRequest #

Read UpdateXMLClassifierRequest Source # 
Show UpdateXMLClassifierRequest Source # 
Generic UpdateXMLClassifierRequest Source # 
Hashable UpdateXMLClassifierRequest Source # 
ToJSON UpdateXMLClassifierRequest Source # 
NFData UpdateXMLClassifierRequest Source # 
type Rep UpdateXMLClassifierRequest Source # 
type Rep UpdateXMLClassifierRequest = D1 * (MetaData "UpdateXMLClassifierRequest" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "UpdateXMLClassifierRequest'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_uxcrClassification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_uxcrRowTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_uxcrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

updateXMLClassifierRequest Source #

Creates a value of UpdateXMLClassifierRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • uxcrClassification - An identifier of the data format that the classifier matches.
  • uxcrRowTag - The XML tag designating the element that contains each record in an XML document being parsed. Note that this cannot identify a self-closing element (closed by /> ). An empty row element that contains only attributes can be parsed as long as it ends with a closing tag (for example, item_a="A" item_b="B"/row is okay, but item_a="A" item_b="B" / is not).
  • uxcrName - The name of the classifier.

uxcrClassification :: Lens' UpdateXMLClassifierRequest (Maybe Text) Source #

An identifier of the data format that the classifier matches.

uxcrRowTag :: Lens' UpdateXMLClassifierRequest (Maybe Text) Source #

The XML tag designating the element that contains each record in an XML document being parsed. Note that this cannot identify a self-closing element (closed by /> ). An empty row element that contains only attributes can be parsed as long as it ends with a closing tag (for example, item_a="A" item_b="B"/row is okay, but item_a="A" item_b="B" / is not).

uxcrName :: Lens' UpdateXMLClassifierRequest Text Source #

The name of the classifier.

UserDefinedFunction

data UserDefinedFunction Source #

Represents the equivalent of a Hive user-defined function (UDF ) definition.

See: userDefinedFunction smart constructor.

Instances

Eq UserDefinedFunction Source # 
Data UserDefinedFunction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserDefinedFunction -> c UserDefinedFunction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserDefinedFunction #

toConstr :: UserDefinedFunction -> Constr #

dataTypeOf :: UserDefinedFunction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserDefinedFunction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserDefinedFunction) #

gmapT :: (forall b. Data b => b -> b) -> UserDefinedFunction -> UserDefinedFunction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedFunction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedFunction -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserDefinedFunction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserDefinedFunction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserDefinedFunction -> m UserDefinedFunction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedFunction -> m UserDefinedFunction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedFunction -> m UserDefinedFunction #

Read UserDefinedFunction Source # 
Show UserDefinedFunction Source # 
Generic UserDefinedFunction Source # 
Hashable UserDefinedFunction Source # 
FromJSON UserDefinedFunction Source # 
NFData UserDefinedFunction Source # 

Methods

rnf :: UserDefinedFunction -> () #

type Rep UserDefinedFunction Source # 
type Rep UserDefinedFunction = D1 * (MetaData "UserDefinedFunction" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "UserDefinedFunction'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_udfOwnerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udfResourceURIs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ResourceURI]))) (S1 * (MetaSel (Just Symbol "_udfFunctionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udfOwnerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PrincipalType))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udfCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_udfClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

userDefinedFunction :: UserDefinedFunction Source #

Creates a value of UserDefinedFunction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

udfOwnerName :: Lens' UserDefinedFunction (Maybe Text) Source #

The owner of the function.

udfResourceURIs :: Lens' UserDefinedFunction [ResourceURI] Source #

The resource URIs for the function.

udfCreateTime :: Lens' UserDefinedFunction (Maybe UTCTime) Source #

The time at which the function was created.

udfClassName :: Lens' UserDefinedFunction (Maybe Text) Source #

The Java class that contains the function code.

UserDefinedFunctionInput

data UserDefinedFunctionInput Source #

A structure used to create or updata a user-defined function.

See: userDefinedFunctionInput smart constructor.

Instances

Eq UserDefinedFunctionInput Source # 
Data UserDefinedFunctionInput Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserDefinedFunctionInput -> c UserDefinedFunctionInput #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserDefinedFunctionInput #

toConstr :: UserDefinedFunctionInput -> Constr #

dataTypeOf :: UserDefinedFunctionInput -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserDefinedFunctionInput) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserDefinedFunctionInput) #

gmapT :: (forall b. Data b => b -> b) -> UserDefinedFunctionInput -> UserDefinedFunctionInput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedFunctionInput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedFunctionInput -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserDefinedFunctionInput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserDefinedFunctionInput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserDefinedFunctionInput -> m UserDefinedFunctionInput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedFunctionInput -> m UserDefinedFunctionInput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedFunctionInput -> m UserDefinedFunctionInput #

Read UserDefinedFunctionInput Source # 
Show UserDefinedFunctionInput Source # 
Generic UserDefinedFunctionInput Source # 
Hashable UserDefinedFunctionInput Source # 
ToJSON UserDefinedFunctionInput Source # 
NFData UserDefinedFunctionInput Source # 
type Rep UserDefinedFunctionInput Source # 
type Rep UserDefinedFunctionInput = D1 * (MetaData "UserDefinedFunctionInput" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "UserDefinedFunctionInput'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_udfiOwnerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_udfiResourceURIs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ResourceURI])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udfiFunctionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udfiOwnerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PrincipalType))) (S1 * (MetaSel (Just Symbol "_udfiClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

userDefinedFunctionInput :: UserDefinedFunctionInput Source #

Creates a value of UserDefinedFunctionInput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

udfiResourceURIs :: Lens' UserDefinedFunctionInput [ResourceURI] Source #

The resource URIs for the function.

udfiClassName :: Lens' UserDefinedFunctionInput (Maybe Text) Source #

The Java class that contains the function code.

XMLClassifier

data XMLClassifier Source #

A classifier for XML content.

See: xmlClassifier smart constructor.

Instances

Eq XMLClassifier Source # 
Data XMLClassifier Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XMLClassifier -> c XMLClassifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XMLClassifier #

toConstr :: XMLClassifier -> Constr #

dataTypeOf :: XMLClassifier -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c XMLClassifier) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XMLClassifier) #

gmapT :: (forall b. Data b => b -> b) -> XMLClassifier -> XMLClassifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XMLClassifier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XMLClassifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> XMLClassifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XMLClassifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XMLClassifier -> m XMLClassifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XMLClassifier -> m XMLClassifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XMLClassifier -> m XMLClassifier #

Read XMLClassifier Source # 
Show XMLClassifier Source # 
Generic XMLClassifier Source # 

Associated Types

type Rep XMLClassifier :: * -> * #

Hashable XMLClassifier Source # 
FromJSON XMLClassifier Source # 
NFData XMLClassifier Source # 

Methods

rnf :: XMLClassifier -> () #

type Rep XMLClassifier Source # 
type Rep XMLClassifier = D1 * (MetaData "XMLClassifier" "Network.AWS.Glue.Types.Product" "amazonka-glue-1.6.0-6lygtbc1qn5L8T6WOf5nFo" False) (C1 * (MetaCons "XMLClassifier'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_xcCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_xcLastUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_xcVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_xcRowTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_xcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_xcClassification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))))

xmlClassifier Source #

Creates a value of XMLClassifier with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • xcCreationTime - The time this classifier was registered.
  • xcLastUpdated - The time this classifier was last updated.
  • xcVersion - The version of this classifier.
  • xcRowTag - The XML tag designating the element that contains each record in an XML document being parsed. Note that this cannot identify a self-closing element (closed by /> ). An empty row element that contains only attributes can be parsed as long as it ends with a closing tag (for example, item_a="A" item_b="B"/row is okay, but item_a="A" item_b="B" / is not).
  • xcName - The name of the classifier.
  • xcClassification - An identifier of the data format that the classifier matches.

xcCreationTime :: Lens' XMLClassifier (Maybe UTCTime) Source #

The time this classifier was registered.

xcLastUpdated :: Lens' XMLClassifier (Maybe UTCTime) Source #

The time this classifier was last updated.

xcVersion :: Lens' XMLClassifier (Maybe Integer) Source #

The version of this classifier.

xcRowTag :: Lens' XMLClassifier (Maybe Text) Source #

The XML tag designating the element that contains each record in an XML document being parsed. Note that this cannot identify a self-closing element (closed by /> ). An empty row element that contains only attributes can be parsed as long as it ends with a closing tag (for example, item_a="A" item_b="B"/row is okay, but item_a="A" item_b="B" / is not).

xcName :: Lens' XMLClassifier Text Source #

The name of the classifier.

xcClassification :: Lens' XMLClassifier Text Source #

An identifier of the data format that the classifier matches.