{-# LANGUAGE OverloadedStrings #-}
module Network.AWS.Athena.Types
(
athena
, _InvalidRequestException
, _TooManyRequestsException
, _InternalServerException
, ColumnNullable (..)
, EncryptionOption (..)
, QueryExecutionState (..)
, ColumnInfo
, columnInfo
, ciScale
, ciPrecision
, ciSchemaName
, ciCatalogName
, ciCaseSensitive
, ciLabel
, ciTableName
, ciNullable
, ciName
, ciType
, Datum
, datum
, dVarCharValue
, EncryptionConfiguration
, encryptionConfiguration
, ecKMSKey
, ecEncryptionOption
, NamedQuery
, namedQuery
, nqNamedQueryId
, nqDescription
, nqName
, nqDatabase
, nqQueryString
, QueryExecution
, queryExecution
, qeStatus
, qeQueryExecutionContext
, qeResultConfiguration
, qeQuery
, qeStatistics
, qeQueryExecutionId
, QueryExecutionContext
, queryExecutionContext
, qecDatabase
, QueryExecutionStatistics
, queryExecutionStatistics
, qesEngineExecutionTimeInMillis
, qesDataScannedInBytes
, QueryExecutionStatus
, queryExecutionStatus
, qesState
, qesStateChangeReason
, qesSubmissionDateTime
, qesCompletionDateTime
, ResultConfiguration
, resultConfiguration
, rcEncryptionConfiguration
, rcOutputLocation
, ResultSet
, resultSet
, rsRows
, rsResultSetMetadata
, ResultSetMetadata
, resultSetMetadata
, rsmColumnInfo
, Row
, row
, rowData
, UnprocessedNamedQueryId
, unprocessedNamedQueryId
, unqiNamedQueryId
, unqiErrorCode
, unqiErrorMessage
, UnprocessedQueryExecutionId
, unprocessedQueryExecutionId
, uqeiErrorCode
, uqeiQueryExecutionId
, uqeiErrorMessage
) where
import Network.AWS.Athena.Types.Product
import Network.AWS.Athena.Types.Sum
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Sign.V4
athena :: Service
athena =
Service
{ _svcAbbrev = "Athena"
, _svcSigner = v4
, _svcPrefix = "athena"
, _svcVersion = "2017-05-18"
, _svcEndpoint = defaultEndpoint athena
, _svcTimeout = Just 70
, _svcCheck = statusSuccess
, _svcError = parseJSONError "Athena"
, _svcRetry = retry
}
where
retry =
Exponential
{ _retryBase = 5.0e-2
, _retryGrowth = 2
, _retryAttempts = 5
, _retryCheck = check
}
check e
| has (hasCode "ThrottledException" . hasStatus 400) e =
Just "throttled_exception"
| has (hasStatus 429) e = Just "too_many_requests"
| has (hasCode "ThrottlingException" . hasStatus 400) e =
Just "throttling_exception"
| has (hasCode "Throttling" . hasStatus 400) e = Just "throttling"
| has (hasStatus 504) e = Just "gateway_timeout"
| has (hasCode "RequestThrottledException" . hasStatus 400) e =
Just "request_throttled_exception"
| has (hasStatus 502) e = Just "bad_gateway"
| has (hasStatus 503) e = Just "service_unavailable"
| has (hasStatus 500) e = Just "general_server_error"
| has (hasStatus 509) e = Just "limit_exceeded"
| otherwise = Nothing
_InvalidRequestException :: AsError a => Getting (First ServiceError) a ServiceError
_InvalidRequestException = _MatchServiceError athena "InvalidRequestException"
_TooManyRequestsException :: AsError a => Getting (First ServiceError) a ServiceError
_TooManyRequestsException = _MatchServiceError athena "TooManyRequestsException"
_InternalServerException :: AsError a => Getting (First ServiceError) a ServiceError
_InternalServerException = _MatchServiceError athena "InternalServerException"