Copyright | (c) 2013-2023 Brendan Hay |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay+amazonka@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Env = Env' Identity
- type EnvNoAuth = Env' Proxy
- data Env' withAuth = Env {}
- newEnv :: MonadIO m => (EnvNoAuth -> m Env) -> m Env
- newEnvFromManager :: MonadIO m => Manager -> (EnvNoAuth -> m Env) -> m Env
- newEnvNoAuth :: MonadIO m => m EnvNoAuth
- newEnvNoAuthFromManager :: MonadIO m => Manager -> m EnvNoAuth
- authMaybe :: Foldable withAuth => Env' withAuth -> Maybe Auth
- overrideService :: (Service -> Service) -> Env' withAuth -> Env' withAuth
- configureService :: Service -> Env' withAuth -> Env' withAuth
- globalTimeout :: Seconds -> Env' withAuth -> Env' withAuth
- once :: Env' withAuth -> Env' withAuth
- runResourceT :: MonadUnliftIO m => ResourceT m a -> m a
- newtype AccessKey = AccessKey ByteString
- newtype SecretKey = SecretKey ByteString
- newtype SessionToken = SessionToken ByteString
- discover :: (MonadCatch m, MonadIO m, Foldable withAuth) => Env' withAuth -> m Env
- newtype Region where
- Region' {
- fromRegion :: Text
- pattern Ningxia :: Region
- pattern Beijing :: Region
- pattern GovCloudWest :: Region
- pattern GovCloudEast :: Region
- pattern SaoPaulo :: Region
- pattern UAE :: Region
- pattern Bahrain :: Region
- pattern Zurich :: Region
- pattern Stockholm :: Region
- pattern Spain :: Region
- pattern Paris :: Region
- pattern Milan :: Region
- pattern London :: Region
- pattern Ireland :: Region
- pattern Frankfurt :: Region
- pattern Montreal :: Region
- pattern Tokyo :: Region
- pattern Sydney :: Region
- pattern Singapore :: Region
- pattern Seoul :: Region
- pattern Osaka :: Region
- pattern Mumbai :: Region
- pattern Melbourne :: Region
- pattern Jakarta :: Region
- pattern Hyderabad :: Region
- pattern HongKong :: Region
- pattern CapeTown :: Region
- pattern Oregon :: Region
- pattern NorthCalifornia :: Region
- pattern NorthVirginia :: Region
- pattern Ohio :: Region
- Region' {
- data Endpoint = Endpoint {
- host :: ByteString
- basePath :: RawPath
- secure :: Bool
- port :: Int
- scope :: ByteString
- setEndpoint :: Bool -> ByteString -> Int -> Service -> Service
- send :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> m (AWSResponse a)
- sendEither :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> m (Either Error (AWSResponse a))
- paginate :: (MonadResource m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> ConduitM () (AWSResponse a) m ()
- paginateEither :: (MonadResource m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> ConduitM () (AWSResponse a) m (Either Error ())
- await :: (MonadResource m, AWSRequest a, Typeable a) => Env -> Wait a -> a -> m Accept
- awaitEither :: (MonadResource m, AWSRequest a, Typeable a) => Env -> Wait a -> a -> m (Either Error Accept)
- sendUnsigned :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env' withAuth -> a -> m (AWSResponse a)
- sendUnsignedEither :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env' withAuth -> a -> m (Either Error (AWSResponse a))
- class ToBody a where
- toBody :: a -> RequestBody
- data RequestBody
- newtype ResponseBody = ResponseBody {
- body :: ConduitM () ByteString (ResourceT IO) ()
- class ToHashedBody a where
- toHashed :: a -> HashedBody
- data HashedBody
- = HashedStream (Digest SHA256) !Integer (ConduitM () ByteString (ResourceT IO) ())
- | HashedBytes (Digest SHA256) ByteString
- hashedFile :: MonadIO m => FilePath -> m HashedBody
- hashedFileRange :: MonadIO m => FilePath -> Integer -> Integer -> m HashedBody
- hashedBody :: Digest SHA256 -> Integer -> ConduitM () ByteString (ResourceT IO) () -> HashedBody
- data ChunkedBody = ChunkedBody {}
- newtype ChunkSize = ChunkSize Int
- defaultChunkSize :: ChunkSize
- chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RequestBody
- chunkedFileRange :: MonadIO m => ChunkSize -> FilePath -> Integer -> Integer -> m RequestBody
- unsafeChunkedBody :: ChunkSize -> Integer -> ConduitM () ByteString (ResourceT IO) () -> RequestBody
- sinkBody :: MonadIO m => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a
- getFileSize :: MonadIO m => FilePath -> m Integer
- sinkMD5 :: forall (m :: Type -> Type) o. Monad m => ConduitM ByteString o m (Digest MD5)
- sinkSHA256 :: forall (m :: Type -> Type) o. Monad m => ConduitM ByteString o m (Digest SHA256)
- presignURL :: (MonadIO m, AWSRequest a) => Env -> UTCTime -> Seconds -> a -> m ByteString
- presign :: (MonadIO m, AWSRequest a) => Env -> UTCTime -> Seconds -> a -> m ClientRequest
- class AsError a where
- class AsAuthError a where
- trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r)
- catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r
- _MatchServiceError :: AsError a => Service -> ErrorCode -> Fold a ServiceError
- hasService :: (Applicative f, Choice p) => Service -> Optic' p f ServiceError ServiceError
- hasStatus :: (Applicative f, Choice p) => Int -> Optic' p f ServiceError ServiceError
- hasCode :: (Applicative f, Choice p) => ErrorCode -> Optic' p f ServiceError ServiceError
- data LogLevel
- type Logger = LogLevel -> ByteStringBuilder -> IO ()
- newLogger :: MonadIO m => LogLevel -> Handle -> m Logger
- data UTCTime
- may :: Applicative f => ([a] -> f b) -> [a] -> f (Maybe b)
- (.!@) :: Functor f => f (Maybe a) -> a -> f a
- nonEmptyText :: Fold a Text -> Fold a Bool
- matchError :: ErrorCode -> Accept -> Acceptor a
- matchStatus :: Int -> Accept -> Acceptor a
- matchNonEmpty :: Bool -> Accept -> Fold (AWSResponse a) b -> Acceptor a
- matchAny :: Eq b => b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
- matchAll :: Eq b => b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
- accept :: Wait a -> Acceptor a
- wait_acceptors :: Lens (Wait a) (Wait b) [Acceptor a] [Acceptor b]
- wait_delay :: Lens' (Wait a) Seconds
- wait_attempts :: Lens' (Wait a) Int
- wait_name :: Lens' (Wait a) ByteString
- type Acceptor a = Request a -> Either Error (ClientResponse (AWSResponse a)) -> Maybe Accept
- data Accept
- data Wait a = Wait {}
- defaultEndpoint :: Service -> Region -> Endpoint
- setEndpoint :: Bool -> ByteString -> Int -> Service -> Service
- decodeError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Either String ServiceError -> Error
- parseRESTError :: Abbrev -> Status -> [Header] -> a -> Error
- parseXMLError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error
- parseJSONError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error
- getErrorCode :: Status -> [Header] -> ErrorCode
- getRequestId :: [Header] -> Maybe RequestId
- serviceError :: Abbrev -> Status -> [Header] -> Maybe ErrorCode -> Maybe ErrorMessage -> Maybe RequestId -> ServiceError
- hasCode :: (Applicative f, Choice p) => ErrorCode -> Optic' p f ServiceError ServiceError
- hasStatus :: (Applicative f, Choice p) => Int -> Optic' p f ServiceError ServiceError
- hasService :: (Applicative f, Choice p) => Service -> Optic' p f ServiceError ServiceError
- _HttpStatus :: AsError a => Traversal' a Status
- statusSuccess :: Status -> Bool
- _MatchServiceError :: AsError a => Service -> ErrorCode -> Fold a ServiceError
- choice :: (Alternative f, ToText a, ToText b) => (s -> f a) -> (s -> f b) -> Getter s (f Text)
- stop :: AWSTruncated a => a -> Bool
- class AWSRequest a => AWSPager a where
- page :: a -> AWSResponse a -> Maybe a
- class AWSTruncated a where
- toMicroseconds :: Seconds -> Int
- toSeconds :: Seconds -> DiffTime
- withAuth :: MonadIO m => Auth -> (AuthEnv -> m a) -> m a
- authEnv_expiration :: Lens' AuthEnv (Maybe ISO8601)
- authEnv_sessionToken :: Lens' AuthEnv (Maybe (Sensitive SessionToken))
- authEnv_secretAccessKey :: Lens' AuthEnv (Sensitive SecretKey)
- authEnv_accessKeyId :: Lens' AuthEnv AccessKey
- _SessionToken :: Iso' SessionToken ByteString
- _SecretKey :: Iso' SecretKey ByteString
- _AccessKey :: Iso' AccessKey ByteString
- requestUnsigned :: Request a -> Region -> ClientRequest
- requestPresign :: Seconds -> Algorithm a
- requestSign :: Algorithm a
- request_body :: Lens' (Request a) RequestBody
- request_headers :: Lens' (Request a) [Header]
- request_query :: Lens' (Request a) QueryString
- request_path :: Lens' (Request a) RawPath
- request_method :: Lens' (Request a) StdMethod
- request_service :: Lens' (Request a) Service
- service_retry :: Lens' Service Retry
- service_error :: Lens' Service (Status -> [Header] -> ByteStringLazy -> Error)
- service_check :: Lens' Service (Status -> Bool)
- service_timeout :: Lens' Service (Maybe Seconds)
- service_endpoint :: Lens' Service (Region -> Endpoint)
- service_endpointPrefix :: Lens' Service ByteString
- service_s3AddressingStyle :: Lens' Service S3AddressingStyle
- service_version :: Lens' Service ByteString
- service_signingName :: Lens' Service ByteString
- service_signer :: Lens' Service Signer
- service_abbrev :: Lens' Service Abbrev
- signed_signedRequest :: Lens' (Signed a) ClientRequest
- signed_signedMeta :: Lens' (Signed a) Meta
- retry_check :: Lens' Retry (ServiceError -> Maybe Text)
- retry_attempts :: Lens' Retry Int
- retry_growth :: Lens' Retry Int
- retry_base :: Lens' Retry Double
- endpoint_scope :: Lens' Endpoint ByteString
- endpoint_port :: Lens' Endpoint Int
- endpoint_secure :: Lens' Endpoint Bool
- endpoint_basePath :: Lens' Endpoint RawPath
- endpoint_host :: Lens' Endpoint ByteString
- serviceError_requestId :: Lens' ServiceError (Maybe RequestId)
- serviceError_message :: Lens' ServiceError (Maybe ErrorMessage)
- serviceError_code :: Lens' ServiceError ErrorCode
- serviceError_headers :: Lens' ServiceError [Header]
- serviceError_status :: Lens' ServiceError Status
- serviceError_abbrev :: Lens' ServiceError Abbrev
- serializeError_message :: Lens' SerializeError String
- serializeError_body :: Lens' SerializeError (Maybe ByteStringLazy)
- serializeError_status :: Lens' SerializeError Status
- serializeError_abbrev :: Lens' SerializeError Abbrev
- _RequestId :: Iso' RequestId Text
- _ErrorMessage :: Iso' ErrorMessage Text
- newErrorCode :: Text -> ErrorCode
- _ErrorCode :: Iso' ErrorCode Text
- _Abbrev :: Iso' Abbrev Text
- newClientRequest :: Endpoint -> Maybe Seconds -> ClientRequest
- type ClientRequest = Request
- type ClientResponse = Response
- type ClientBody = ConduitM () ByteString (ResourceT IO) ()
- data Abbrev
- newtype ErrorCode = ErrorCode Text
- newtype ErrorMessage = ErrorMessage {}
- newtype RequestId = RequestId {}
- data Error
- data SerializeError = SerializeError' {}
- data ServiceError = ServiceError' {}
- class AsError a where
- data Endpoint = Endpoint {
- host :: ByteString
- basePath :: RawPath
- secure :: Bool
- port :: Int
- scope :: ByteString
- data Retry = Exponential {}
- data Meta where
- data Signed a = Signed {}
- type Algorithm a = Request a -> AuthEnv -> Region -> UTCTime -> Signed a
- data Signer = Signer (forall a. Algorithm a) (forall a. Seconds -> Algorithm a)
- data Service = Service {
- abbrev :: Abbrev
- signer :: Signer
- signingName :: ByteString
- version :: ByteString
- s3AddressingStyle :: S3AddressingStyle
- endpointPrefix :: ByteString
- endpoint :: Region -> Endpoint
- timeout :: Maybe Seconds
- check :: Status -> Bool
- error :: Status -> [Header] -> ByteStringLazy -> Error
- retry :: Retry
- data S3AddressingStyle
- data Request a = Request {}
- type family AWSResponse a
- class AWSRequest a where
- type AWSResponse a
- request :: (Service -> Service) -> a -> Request a
- response :: MonadResource m => (ByteStringLazy -> IO ByteStringLazy) -> Service -> Proxy a -> ClientResponse ClientBody -> m (Either Error (ClientResponse (AWSResponse a)))
- newtype AccessKey = AccessKey ByteString
- newtype SecretKey = SecretKey ByteString
- newtype SessionToken = SessionToken ByteString
- data AuthEnv = AuthEnv {}
- data Auth
- newtype Region where
- Region' {
- fromRegion :: Text
- pattern Ohio :: Region
- pattern NorthVirginia :: Region
- pattern NorthCalifornia :: Region
- pattern Oregon :: Region
- pattern CapeTown :: Region
- pattern HongKong :: Region
- pattern Hyderabad :: Region
- pattern Jakarta :: Region
- pattern Melbourne :: Region
- pattern Mumbai :: Region
- pattern Osaka :: Region
- pattern Seoul :: Region
- pattern Singapore :: Region
- pattern Sydney :: Region
- pattern Tokyo :: Region
- pattern Montreal :: Region
- pattern Frankfurt :: Region
- pattern Ireland :: Region
- pattern London :: Region
- pattern Milan :: Region
- pattern Paris :: Region
- pattern Spain :: Region
- pattern Stockholm :: Region
- pattern Zurich :: Region
- pattern Bahrain :: Region
- pattern UAE :: Region
- pattern SaoPaulo :: Region
- pattern GovCloudEast :: Region
- pattern GovCloudWest :: Region
- pattern Beijing :: Region
- pattern Ningxia :: Region
- Region' {
- newtype Seconds = Seconds DiffTime
- _Base64 :: Iso' Base64 ByteString
- newtype Base64 = Base64 {}
- _Sensitive :: Iso' (Sensitive a) a
- newtype Sensitive a = Sensitive {
- fromSensitive :: a
- contentLength :: RequestBody -> Integer
- toRequestBody :: RequestBody -> RequestBody
- isStreaming :: RequestBody -> Bool
- md5Base64 :: RequestBody -> Maybe ByteString
- hashedBody :: Digest SHA256 -> Integer -> ConduitM () ByteString (ResourceT IO) () -> HashedBody
- hashedFileRange :: MonadIO m => FilePath -> Integer -> Integer -> m HashedBody
- hashedFile :: MonadIO m => FilePath -> m HashedBody
- sha256Base16 :: HashedBody -> ByteString
- sourceFileRangeChunks :: forall (m :: Type -> Type). MonadResource m => ChunkSize -> FilePath -> Integer -> Integer -> ConduitM () ByteString m ()
- sourceFileChunks :: forall (m :: Type -> Type). MonadResource m => ChunkSize -> FilePath -> ConduitM () ByteString m ()
- unsafeChunkedBody :: ChunkSize -> Integer -> ConduitM () ByteString (ResourceT IO) () -> RequestBody
- chunkedFileRange :: MonadIO m => ChunkSize -> FilePath -> Integer -> Integer -> m RequestBody
- chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RequestBody
- remainderBytes :: ChunkedBody -> Maybe Integer
- fullChunks :: ChunkedBody -> Integer
- fuseChunks :: ChunkedBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ChunkedBody
- chunkedBody_body :: Lens' ChunkedBody (ConduitM () ByteString (ResourceT IO) ())
- chunkedBody_length :: Lens' ChunkedBody Integer
- chunkedBody_size :: Lens' ChunkedBody ChunkSize
- defaultChunkSize :: ChunkSize
- _ChunkSize :: Iso' ChunkSize Int
- sinkBody :: MonadIO m => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a
- fuseStream :: ResponseBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ResponseBody
- _ResponseBody :: Iso' ResponseBody (ConduitM () ByteString (ResourceT IO) ())
- getFileSize :: MonadIO m => FilePath -> m Integer
- newtype ResponseBody = ResponseBody {
- body :: ConduitM () ByteString (ResourceT IO) ()
- newtype ChunkSize = ChunkSize Int
- data ChunkedBody = ChunkedBody {}
- data HashedBody
- = HashedStream (Digest SHA256) !Integer (ConduitM () ByteString (ResourceT IO) ())
- | HashedBytes (Digest SHA256) ByteString
- data RequestBody
- class ToHashedBody a where
- toHashed :: a -> HashedBody
- class ToBody a where
- toBody :: a -> RequestBody
- buildLines :: [ByteStringBuilder] -> ByteStringBuilder
- class ToLog a where
- build :: a -> ByteStringBuilder
- _Time :: forall (a :: Format). Iso' (Time a) UTCTime
- data Format
- newtype Time (a :: Format) = Time {}
- type RFC822 = Time 'RFC822Format
- type ISO8601 = Time 'ISO8601Format
- type BasicTime = Time 'BasicFormat
- type AWSTime = Time 'AWSFormat
- type POSIX = Time 'POSIXFormat
- data HttpException
Usage
The key functions dealing with the request/response lifecycle are:
These functions have constraints that types from the amazonka-*
libraries
satisfy. To utilise these, you will need to specify what Region
you wish to
operate in and your Amazon credentials for AuthN/AuthZ purposes.
Credentials can be supplied in a number of ways. Either via explicit keys, via session profiles, or have Amazonka retrieve the credentials from an underlying IAM Role/Profile.
As a basic example, you might wish to store an object in an S3 bucket using amazonka-s3:
{-# LANGUAGE OverloadedStrings #-} import qualified Amazonka as AWS import qualified Amazonka.S3 as S3 import qualified System.IO as IO example :: IO S3.PutObjectResponse example = do -- A newLogger
to replace the default noop logger is created, with the logger -- set to print debug information and errors to stdout: logger <- AWS.newLogger
AWS.Debug
IO.stdout -- To specify configuration preferences,newEnv
is used to create a new -- configuration environment. The argument tonewEnv
is used to specify the -- mechanism for supplying or retrieving AuthN/AuthZ information. -- In this casediscover
will cause the library to try a number of options such -- as default environment variables, or an instance's IAM Profile and identity document: discoveredEnv <- AWS.newEnv
AWS.discover
let env = discoveredEnv { AWS.logger = logger , AWS.region = AWS.Frankfurt
} -- The payload (and hash) for the S3 object is retrieved from aFilePath
, -- eitherhashedFile
orchunkedFile
can be used, with the latter ensuring -- the contents of the file is enumerated exactly once, during send: body <- AWS.chunkedFile AWS.defaultChunkSize "local/path/to/object-payload" -- We now run theAWS
computation with the overriden logger, performing the --PutObject
request. AWS.runResourceT $ AWS.send
env (S3.newPutObject "bucket-name" "object-key" body)
Authentication and Environment
type Env = Env' Identity Source #
An environment with auth credentials. Most AWS requests need one
of these, and you can create one with newEnv
.
type EnvNoAuth = Env' Proxy Source #
An environment with no auth credentials. Used for certain
requests which need to be unsigned, like
sts:AssumeRoleWithWebIdentity
, and you can create one with
newEnvNoAuth
if you need it.
The environment containing the parameters required to make AWS requests.
This type tracks whether or not we have credentials at the type level, to avoid "presigning" requests when we lack auth information.
Instances
Creates a new environment with a new Manager
without
debug logging and uses the provided function to expand/discover
credentials. Record updates or lenses can be used to further
configure the resulting Env
.
Since: 1.5.0
- The region is now retrieved from the AWS_REGION
environment
variable (identical to official SDKs), or defaults to us-east-1
.
You can override the Env
region by updating its $sel:region:Env
field.
Since: 1.3.6
- The default logic for retrying HttpException
s now uses
retryConnectionFailure
to retry specific connection failure conditions up to 3 times.
Previously only service specific errors were automatically retried.
This can be reverted to the old behaviour by resetting the Env'
s
$sel:retryCheck:Env
field to (\_ _ -> False)
.
Throws AuthError
when environment variables or IAM profiles cannot be read.
See: newEnvFromManager
.
Creates a new environment, but with an existing Manager
.
newEnvNoAuth :: MonadIO m => m EnvNoAuth Source #
Generate an environment without credentials, which may only make
unsigned requests. Sets the region based on the AWS_REGION
environment variable, or NorthVirginia
if unset.
This lets us support calls like the sts:AssumeRoleWithWebIdentity operation, which needs to make an unsigned request to pass the token from an identity provider.
newEnvNoAuthFromManager :: MonadIO m => Manager -> m EnvNoAuth Source #
Generate an environment without credentials, passing in an
explicit Manager
.
Service Configuration
When a request is sent, various values such as the endpoint,
retry strategy, timeout and error handlers are taken from the associated Service
for a request. For example, DynamoDB
will use the defaultService
configuration when sending PutItem
, Query
and all other operations.
You can modify a specific Service'
s default configuration by using
configureService
. To modify all configurations simultaneously, see
overrideService
.
An example of how you might alter default configuration using these mechanisms
is demonstrated below. Firstly, the default dynamoDB
service is configured to
use non-SSL localhost as the endpoint:
import qualified Amazonka as AWS import qualified Amazonka.DynamoDB as DynamoDB let dynamo :: AWS.Service dynamo = AWS.setEndpoint False "localhost" 8000 DynamoDB.defaultService
The updated configuration is then passed to the Env
during setup:
env <- AWS.configureService
dynamo <$> AWS.newEnv
AWS.discover
AWS.runResourceT $ do -- This S3 operation will communicate with remote AWS APIs. x <- AWS.send env newListBuckets -- DynamoDB operations will communicate with localhost:8000. y <- AWS.send env Dynamo.newListTables -- Any operations for services other than DynamoDB, are not affected. ...
You can also scope the service configuration modifications to specific actions:
env <- AWS.newEnv
AWS.discover
AWS.runResourceT $ do -- Service operations here will communicate with AWS, even remote DynamoDB. x <- AWS.send env Dynamo.newListTables -- Here DynamoDB operations will communicate with localhost:8000. y <- AWS.send (AWS.configure dynamo env) Dynamo.newListTables
Functions such as once
and globalTimeout
can
also be used to modify service configuration for all (or specific)
requests.
overrideService :: (Service -> Service) -> Env' withAuth -> Env' withAuth Source #
Provide a function which will be added to the existing stack of overrides applied to all service configurations.
configureService :: Service -> Env' withAuth -> Env' withAuth Source #
Configure a specific service. All requests belonging to the supplied service will use this configuration instead of the default.
It's suggested you modify the default service configuration,
such as Amazonka.DynamoDB.defaultService
.
globalTimeout :: Seconds -> Env' withAuth -> Env' withAuth Source #
Override the timeout value for this Env
.
Default timeouts are chosen by considering:
- This
timeout
, if set. - The related
Service
timeout for the sent request if set. (Usually 70s) - The
$sel:manager:Env
timeout if set. - The default
ClientRequest
timeout. (Approximately 30s)
once :: Env' withAuth -> Env' withAuth Source #
Disable any retry logic for an Env
, so that any requests will
at most be sent once.
Running AWS Actions
runResourceT :: MonadUnliftIO m => ResourceT m a -> m a #
Unwrap a ResourceT
transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO
.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT
will deallocate the resources.
NOTE Since version 1.2.0, this function will throw a
ResourceCleanupException
if any of the cleanup functions throw an
exception.
Since: resourcet-0.3.0
Credential Discovery
AuthN/AuthZ information is handled similarly to other AWS SDKs. You can read some of the options available here.
discover
should be your default way of requesting credentials, as it searches the
standard places that the official AWS SDKs use.
Authentication methods which return short-lived credentials (e.g., when running on
an EC2 instance) fork a background thread which transparently handles the expiry
and subsequent refresh of IAM profile information. See
fetchAuthInBackground
for more information.
See: Amazonka.Auth, if you want to commit to specific authentication methods.
See: runCredentialChain
if you want to build your own credential chain.
An access key ID.
For example: AKIAIOSFODNN7EXAMPLE
Instances
FromJSON AccessKey | |
ToJSON AccessKey | |
Defined in Amazonka.Types | |
ToByteString AccessKey | |
Defined in Amazonka.Types toBS :: AccessKey -> ByteString # | |
ToLog AccessKey | |
Defined in Amazonka.Types build :: AccessKey -> ByteStringBuilder # | |
ToQuery AccessKey | |
Defined in Amazonka.Types toQuery :: AccessKey -> QueryString # | |
FromText AccessKey | |
ToText AccessKey | |
Defined in Amazonka.Types | |
FromXML AccessKey | |
ToXML AccessKey | |
Defined in Amazonka.Types | |
IsString AccessKey | |
Defined in Amazonka.Types fromString :: String -> AccessKey # | |
Generic AccessKey | |
Read AccessKey | |
Show AccessKey | |
NFData AccessKey | |
Defined in Amazonka.Types | |
Eq AccessKey | |
Hashable AccessKey | |
Defined in Amazonka.Types | |
type Rep AccessKey | |
Defined in Amazonka.Types type Rep AccessKey = D1 ('MetaData "AccessKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "AccessKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Secret access key credential.
For example: wJalrXUtnFEMIK7MDENGbPxRfiCYEXAMPLEKE
Instances
FromJSON SecretKey | |
ToJSON SecretKey | |
Defined in Amazonka.Types | |
ToByteString SecretKey | |
Defined in Amazonka.Types toBS :: SecretKey -> ByteString # | |
FromText SecretKey | |
ToText SecretKey | |
Defined in Amazonka.Types | |
FromXML SecretKey | |
ToXML SecretKey | |
Defined in Amazonka.Types | |
IsString SecretKey | |
Defined in Amazonka.Types fromString :: String -> SecretKey # | |
Generic SecretKey | |
NFData SecretKey | |
Defined in Amazonka.Types | |
Eq SecretKey | |
Hashable SecretKey | |
Defined in Amazonka.Types | |
type Rep SecretKey | |
Defined in Amazonka.Types type Rep SecretKey = D1 ('MetaData "SecretKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "SecretKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
newtype SessionToken #
A session token used by STS to temporarily authorise access to an AWS resource.
Instances
discover :: (MonadCatch m, MonadIO m, Foldable withAuth) => Env' withAuth -> m Env Source #
Attempt to fetch credentials in a way similar to the official AWS SDKs. The C++ SDK lists the following sequence:
- Check environment variables for keys provided directly
(
AWS_ACCESS_KEY_ID
,AWS_SECRET_ACCESS_KEY
, optionallyAWS_SESSION_TOKEN
) - Check credentials/config files for authentication information,
respecting the
AWS_PROFILE
environment variable. - Exchange a Web Identity for AWS Credentials using
sts:AssumeRoleWithWebIdentity
, respecting theAWS_WEB_IDENTITY_TOKEN_FILE
,AWS_ROLE_ARN
, and optionally theAWS_ROLE_SESSION_NAME
environment variables. - Retrieve credentials from the ECS Container Agent if the
AWS_CONTAINER_CREDENTIALS_RELATIVE_URI
environment variable is set. If we think we're running on EC2, retrieve the first available IAM profile from the instance identity document, and use this to set the
Placement
. We attempt to resolve http://instance-data rather than directly retrieving http://169.254.169.254 for IAM profile information. This ensures that the DNS lookup terminates promptly if not running on EC2, but means that your VPC must haveenableDnsSupport
andenableDnsHostnames
set.NOTE: This is not 100% consistent with the AWS SDKs, which does not attempt to query the ECS service if either
AWS_CONTAINER_CREDENTIALS_RELATIVE_URI
orAWS_CONTAINER_CREDENTIALS_FULL_URI
are set.
Supported Regions
The available AWS regions.
pattern Ningxia :: Region | |
pattern Beijing :: Region | |
pattern GovCloudWest :: Region | |
pattern GovCloudEast :: Region | |
pattern SaoPaulo :: Region | |
pattern UAE :: Region | |
pattern Bahrain :: Region | |
pattern Zurich :: Region | |
pattern Stockholm :: Region | |
pattern Spain :: Region | |
pattern Paris :: Region | |
pattern Milan :: Region | |
pattern London :: Region | |
pattern Ireland :: Region | |
pattern Frankfurt :: Region | |
pattern Montreal :: Region | |
pattern Tokyo :: Region | |
pattern Sydney :: Region | |
pattern Singapore :: Region | |
pattern Seoul :: Region | |
pattern Osaka :: Region | |
pattern Mumbai :: Region | |
pattern Melbourne :: Region | |
pattern Jakarta :: Region | |
pattern Hyderabad :: Region | |
pattern HongKong :: Region | |
pattern CapeTown :: Region | |
pattern Oregon :: Region | |
pattern NorthCalifornia :: Region | |
pattern NorthVirginia :: Region | |
pattern Ohio :: Region |
Instances
FromJSON Region | |
ToJSON Region | |
Defined in Amazonka.Types | |
ToByteString Region | |
Defined in Amazonka.Types toBS :: Region -> ByteString # | |
ToLog Region | |
Defined in Amazonka.Types build :: Region -> ByteStringBuilder # | |
ToQuery Region | |
Defined in Amazonka.Types toQuery :: Region -> QueryString # | |
FromText Region | |
ToText Region | |
Defined in Amazonka.Types | |
FromXML Region | |
ToXML Region | |
Defined in Amazonka.Types | |
IsString Region | |
Defined in Amazonka.Types fromString :: String -> Region # | |
Generic Region | |
Read Region | |
Show Region | |
NFData Region | |
Defined in Amazonka.Types | |
Eq Region | |
Ord Region | |
Hashable Region | |
Defined in Amazonka.Types | |
type Rep Region | |
Defined in Amazonka.Types |
Service Endpoints
Endpoint | |
|
Instances
Generic Endpoint | |
Show Endpoint | |
Eq Endpoint | |
type Rep Endpoint | |
Defined in Amazonka.Types type Rep Endpoint = D1 ('MetaData "Endpoint" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "Endpoint" 'PrefixI 'True) ((S1 ('MetaSel ('Just "host") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "basePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RawPath)) :*: (S1 ('MetaSel ('Just "secure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "port") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "scope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))) |
:: Bool | Whether to use HTTPS (ie. SSL). |
-> ByteString | The hostname to connect to. |
-> Int | The port number to connect to. |
-> Service | The service configuration to override. |
-> Service |
A convenience function for overriding the Service
Endpoint
.
See: $sel:endpoint:Service
.
Sending Requests
To send a request you need to create a value of the desired operation type using
the relevant constructor, as well as any further modifications of default/optional
parameters using the appropriate lenses. This value can then be sent using send
or paginate
and the library will take care of serialisation/authentication and
so forth.
The default Service
configuration for a request contains retry configuration that is used to
determine if a request can safely be retried and what kind of back off/on strategy
should be used. (Usually exponential.)
Typically services define retry strategies that handle throttling, general server
errors and transport errors. Streaming requests are never retried.
send :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> m (AWSResponse a) Source #
Send a request, returning the associated response if successful.
Errors are thrown in IO
.
See sendEither
.
sendEither :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> m (Either Error (AWSResponse a)) Source #
Send a request, returning the associated response if successful.
See send
.
Pagination
Some AWS operations return results that are incomplete and require subsequent
requests in order to obtain the entire result set. The process of sending
subsequent requests to continue where a previous request left off is called
pagination. For example, the ListObjects
operation of Amazon S3 returns up to
1000 objects at a time, and you must send subsequent requests with the
appropriate Marker in order to retrieve the next page of results.
Operations that have an AWSPager
instance can transparently perform subsequent
requests, correctly setting markers and other request facets to iterate through
the entire result set of a truncated API operation. Operations which support
this have an additional note in the documentation.
Many operations have the ability to filter results on the server side. See the individual operation parameters for details.
paginate :: (MonadResource m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> ConduitM () (AWSResponse a) m () Source #
Repeatedly send a request, automatically setting markers and performing pagination. Exits on the first encountered error.
Errors are thrown in IO
.
See paginateEither
.
paginateEither :: (MonadResource m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> ConduitM () (AWSResponse a) m (Either Error ()) Source #
Repeatedly send a request, automatically setting markers and performing pagination.
Exits on the first encountered error.
See paginate
.
Waiters
Waiters poll by repeatedly sending a request until some remote success condition
configured by the Wait
specification is fulfilled. The Wait
specification
determines how many attempts should be made, in addition to delay and retry strategies.
Error conditions that are not handled by the Wait
configuration will be thrown,
or the first successful response that fulfills the success condition will be
returned.
Wait
specifications can be found under the Amazonka.{ServiceName}.Waiters
namespace for services which support await
.
await :: (MonadResource m, AWSRequest a, Typeable a) => Env -> Wait a -> a -> m Accept Source #
Poll the API with the supplied request until a specific Wait
condition
is fulfilled.
Errors are thrown in IO
.
See awaitEither
.
awaitEither :: (MonadResource m, AWSRequest a, Typeable a) => Env -> Wait a -> a -> m (Either Error Accept) Source #
Poll the API with the supplied request until a specific Wait
condition
is fulfilled.
See await
.
Unsigned
sendUnsigned :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env' withAuth -> a -> m (AWSResponse a) Source #
Make an unsigned request, returning the associated response if successful.
Errors are thrown in IO
.
See sendUnsignedEither
.
sendUnsignedEither :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env' withAuth -> a -> m (Either Error (AWSResponse a)) Source #
Make a request without signing it. You will almost never need to
do this, but some authentication methods
(e.g. sts:AssumeRoleWithWebIdentity
and sso:GetRoleCredentials
)
require you to exchange a token using an unsigned
request. Amazonka's support for these authentication methods calls
sendUnsigned
, and we re-export these functions in case you need
to support similar authentication methods in your code.
See sendUnsigned
.
Streaming
Streaming comes in two flavours. HashedBody
represents a request
that requires a precomputed SHA256
hash, or a ChunkedBody
type for those services
that can perform incremental signing and do not require the entire payload to
be hashed (such as S3). The type signatures for request smart constructors
advertise which respective body type is required, denoting the underlying signing
capabilities.
ToHashedBody
and ToBody
typeclass instances are available to construct the
streaming bodies, automatically calculating any hash or size as needed for types
such as Text
, ByteString
, or Aeson's Value
type. To read files and other
IO
primitives, functions such as hashedFile
, chunkedFile
, or hashedBody
should be used.
For responses that contain streaming bodies (such as GetObject
), you can use
sinkBody
to connect the response body to a
conduit-compatible sink.
Anything that can be converted to a streaming request Body
.
Nothing
toBody :: a -> RequestBody #
Convert a value to a request body.
Instances
data RequestBody #
Invariant: only services that support both standard and
chunked signing expose RequestBody
as a parameter.
Chunked ChunkedBody | Currently S3 only, see |
Hashed HashedBody |
Instances
ToBody RequestBody | |
Defined in Amazonka.Data.Body toBody :: RequestBody -> RequestBody # | |
IsString RequestBody | |
Defined in Amazonka.Data.Body fromString :: String -> RequestBody # | |
Show RequestBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> RequestBody -> ShowS # show :: RequestBody -> String # showList :: [RequestBody] -> ShowS # |
newtype ResponseBody #
A streaming, exception safe response body.
newtype
for show/orhpan instance purposes.
ResponseBody | |
|
Instances
Generic ResponseBody | |
Defined in Amazonka.Data.Body type Rep ResponseBody :: Type -> Type # from :: ResponseBody -> Rep ResponseBody x # to :: Rep ResponseBody x -> ResponseBody # | |
Show ResponseBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> ResponseBody -> ShowS # show :: ResponseBody -> String # showList :: [ResponseBody] -> ShowS # | |
type Rep ResponseBody | |
Defined in Amazonka.Data.Body type Rep ResponseBody = D1 ('MetaData "ResponseBody" "Amazonka.Data.Body" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "ResponseBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConduitM () ByteString (ResourceT IO) ())))) |
Hashed Request Bodies
class ToHashedBody a where #
Anything that can be safely converted to a HashedBody
.
toHashed :: a -> HashedBody #
Convert a value to a hashed request body.
Instances
ToHashedBody Value | |
Defined in Amazonka.Data.Body toHashed :: Value -> HashedBody # | |
ToHashedBody Base64 | |
Defined in Amazonka.Data.Base64 toHashed :: Base64 -> HashedBody # | |
ToHashedBody HashedBody | |
Defined in Amazonka.Data.Body toHashed :: HashedBody -> HashedBody # | |
ToHashedBody QueryString | |
Defined in Amazonka.Data.Body toHashed :: QueryString -> HashedBody # | |
ToHashedBody ByteStringLazy | |
Defined in Amazonka.Data.Body toHashed :: ByteStringLazy -> HashedBody # | |
ToHashedBody TextLazy | |
Defined in Amazonka.Data.Body toHashed :: TextLazy -> HashedBody # | |
ToHashedBody ByteString | |
Defined in Amazonka.Data.Body toHashed :: ByteString -> HashedBody # | |
ToHashedBody Text | |
Defined in Amazonka.Data.Body toHashed :: Text -> HashedBody # | |
ToHashedBody Element | |
Defined in Amazonka.Data.Body toHashed :: Element -> HashedBody # | |
ToHashedBody String | |
Defined in Amazonka.Data.Body toHashed :: String -> HashedBody # | |
ToHashedBody (KeyMap Value) | |
Defined in Amazonka.Data.Body toHashed :: KeyMap Value -> HashedBody # |
data HashedBody #
An opaque request body containing a SHA256
hash.
HashedStream (Digest SHA256) !Integer (ConduitM () ByteString (ResourceT IO) ()) | |
HashedBytes (Digest SHA256) ByteString |
Instances
ToBody HashedBody | |
Defined in Amazonka.Data.Body toBody :: HashedBody -> RequestBody # | |
ToHashedBody HashedBody | |
Defined in Amazonka.Data.Body toHashed :: HashedBody -> HashedBody # | |
IsString HashedBody | |
Defined in Amazonka.Data.Body fromString :: String -> HashedBody # | |
Show HashedBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> HashedBody -> ShowS # show :: HashedBody -> String # showList :: [HashedBody] -> ShowS # |
:: MonadIO m | |
=> FilePath | The file path to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, calculating the SHA256
hash
and file size.
Note: While this function will perform in constant space, it will enumerate the entirety of the file contents twice. Firstly to calculate the SHA256 and lastly to stream the contents to the socket during sending.
See: ToHashedBody
.
:: MonadIO m | |
=> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: hashedFile
, sourceFileRange
.
:: Digest SHA256 | A SHA256 hash of the file contents. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> HashedBody |
Construct a HashedBody
from a Source
, manually specifying the SHA256
hash and file size. It's left up to the caller to calculate these correctly,
otherwise AWS will return signing errors.
See: ToHashedBody
.
Chunked Request Bodies
data ChunkedBody #
An opaque request body which will be transmitted via
Transfer-Encoding: chunked
.
Invariant: Only services that support chunked encoding can
accept a ChunkedBody
. (Currently S3.) This is enforced by the type
signatures emitted by the generator.
Instances
ToBody ChunkedBody | |
Defined in Amazonka.Data.Body toBody :: ChunkedBody -> RequestBody # | |
Show ChunkedBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> ChunkedBody -> ShowS # show :: ChunkedBody -> String # showList :: [ChunkedBody] -> ShowS # |
Specifies the transmitted size of the 'Transfer-Encoding' chunks.
See: defaultChunk
.
Instances
ToLog ChunkSize | |
Defined in Amazonka.Data.Body build :: ChunkSize -> ByteStringBuilder # | |
Enum ChunkSize | |
Defined in Amazonka.Data.Body succ :: ChunkSize -> ChunkSize # pred :: ChunkSize -> ChunkSize # fromEnum :: ChunkSize -> Int # enumFrom :: ChunkSize -> [ChunkSize] # enumFromThen :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromTo :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromThenTo :: ChunkSize -> ChunkSize -> ChunkSize -> [ChunkSize] # | |
Num ChunkSize | |
Integral ChunkSize | |
Defined in Amazonka.Data.Body | |
Real ChunkSize | |
Defined in Amazonka.Data.Body toRational :: ChunkSize -> Rational # | |
Show ChunkSize | |
Eq ChunkSize | |
Ord ChunkSize | |
Defined in Amazonka.Data.Body |
defaultChunkSize :: ChunkSize #
The default chunk size of 128 KB. The minimum chunk size accepted by AWS is 8 KB, unless the entirety of the request is below this threshold.
A chunk size of 64 KB or higher is recommended for performance reasons.
chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RequestBody #
Construct a ChunkedBody
from a FilePath
, where the contents will be
read and signed incrementally in chunks if the target service supports it.
Will intelligently revert to HashedBody
if the file is smaller than the
specified ChunkSize
.
See: ToBody
.
:: MonadIO m | |
=> ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m RequestBody |
Construct a ChunkedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: chunkedFile
.
:: ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> RequestBody |
Unsafely construct a ChunkedBody
.
This function is marked unsafe because it does nothing to enforce the chunk size.
Typically for conduit IO
functions, it's whatever ByteString's
defaultBufferSize
is, around 32 KB. If the chunk size is less than 8 KB,
the request will error. 64 KB or higher chunk size is recommended for
performance reasons.
Note that it will always create a chunked body even if the request is too small.
See: ToBody
.
Response Bodies
sinkBody :: MonadIO m => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a #
Connect a Sink
to a response stream.
File Size and MD5/SHA256
getFileSize :: MonadIO m => FilePath -> m Integer #
Convenience function for obtaining the size of a file.
sinkMD5 :: forall (m :: Type -> Type) o. Monad m => ConduitM ByteString o m (Digest MD5) #
Incrementally calculate a MD5
Digest
.
sinkSHA256 :: forall (m :: Type -> Type) o. Monad m => ConduitM ByteString o m (Digest SHA256) #
Incrementally calculate a SHA256
Digest
.
Presigning Requests
Presigning requires the Service
signer to be an instance of AWSPresigner
.
Not all signing algorithms support this.
:: (MonadIO m, AWSRequest a) | |
=> Env | |
-> UTCTime | Signing time. |
-> Seconds | Expiry time. |
-> a | Request to presign. |
-> m ByteString |
Presign an URL that is valid from the specified time until the number of seconds expiry has elapsed.
:: (MonadIO m, AWSRequest a) | |
=> Env | |
-> UTCTime | Signing time. |
-> Seconds | Expiry time. |
-> a | Request to presign. |
-> m ClientRequest |
Presign an HTTP request that is valid from the specified time until the number of seconds expiry has elapsed.
Running Asynchronous Actions
Requests can be sent asynchronously, but due to guarantees about resource closure require the use of UnliftIO.Async.
The following example demonstrates retrieving two objects from S3 concurrently:
{-# LANGUAGE OverloadedStrings #-} import qualified Amazonka as AWS import qualified Amazonka.S3 as S3 import qualified UnliftIO.Async as Async let requestA = S3.newGetObject "bucket" "prefix/object-a" let requestB = S3.newGetObject "bucket" "prefix/object-b" runResourceT $ Async.withAsync
(send env requestA) $ \asyncA -> Async.withAsync
(send env requestB) $ \asyncB -> do Async.waitBoth
asyncA asyncB
If you are running many async requests in parallel, using
ContT
can hide the giant callback pyramid:
runResourceT .evalContT
$ do asyncA <- ContT $ Async.withAsync
(send env requestA) asyncB <- ContT $ Async.withAsync
(send env requestB) Async.waitBoth
asyncA asyncB
Handling Errors
Errors are either returned or thrown by the library using IO
. Sub-errors of
the canonical LogLevel
type can be caught using trying
or catching
and the
appropriate AsError
Prism
when using the non-Either
send variants:
trying_Error
(send $ newListObjects "bucket-name") :: EitherError
ListObjectsResponse trying_TransportError
(send $ newListObjects "bucket-name") :: EitherHttpException
ListObjectsResponse trying_SerializeError
(send $ newListObjects "bucket-name") :: EitherSerializeError
ListObjectsResponse trying_ServiceError
(send $ newListObjects "bucket-name") :: EitherServiceError
ListObjectsResponse
Many of the individual amazonka-*
libraries export compatible Fold
s for
matching service specific error codes and messages in the style above.
See the Error Matchers
heading in each respective library for details.
A general Amazonka error.
_TransportError :: Prism' a HttpException #
An error occured while communicating over HTTP with a remote service.
_SerializeError :: Prism' a SerializeError #
A serialisation error occured when attempting to deserialise a response.
_ServiceError :: Prism' a ServiceError #
A service specific error returned by the remote service.
Instances
AsError Error | |
Defined in Amazonka.Types | |
AsError SomeException | |
class AsAuthError a where Source #
_AuthError :: Prism' a AuthError Source #
A general authentication error.
_RetrievalError :: Prism' a HttpException Source #
An error occured while communicating over HTTP with the local metadata endpoint.
_MissingEnvError :: Prism' a Text Source #
The named environment variable was not found.
_MissingFileError :: Prism' a FilePath Source #
The specified credentials file could not be found.
_InvalidFileError :: Prism' a Text Source #
An error occured parsing the credentials file.
_InvalidIAMError :: Prism' a Text Source #
The specified IAM profile could not be found or deserialised.
Instances
AsAuthError AuthError Source # | |
AsAuthError SomeException Source # | |
Defined in Amazonka.Auth.Exception |
trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r) #
A variant of try
that takes a ReifiedPrism
(or any ReifiedFold
) to select which
exceptions are caught (c.f. tryJust
, catchJust
). If the
Exception
does not match the predicate, it is re-thrown.
trying
::MonadCatch
m =>Prism'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Lens'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Iso'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> m (Either
a r)
catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r #
Catch exceptions that match a given ReifiedPrism
(or any ReifiedFold
, really).
>>>
catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
catching
::MonadCatch
m =>Prism'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Lens'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Iso'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> (a -> m r) -> m r
Building Error Prisms
_MatchServiceError :: AsError a => Service -> ErrorCode -> Fold a ServiceError #
Provides a generalised prism for catching a specific service error identified by the opaque service abbreviation and error code.
This can be used if the generated error prisms provided by
Amazonka.ServiceName.Types
do not cover all the thrown error codes.
For example to define a new error prism:
{-# LANGUAGE OverloadedStrings #-} import Amazonka.S3 (ServiceError, s3) _NoSuchBucketPolicy :: AsError a => Fold a ServiceError _NoSuchBucketPolicy = _MatchServiceError s3 "NoSuchBucketPolicy"
With example usage being:
>>>
import Control.Exception.Lens (trying)
>>>
:t trying _NoSuchBucketPolicy
MonadCatch m => m a -> m (Either ServiceError a)
hasService :: (Applicative f, Choice p) => Service -> Optic' p f ServiceError ServiceError #
hasStatus :: (Applicative f, Choice p) => Int -> Optic' p f ServiceError ServiceError #
hasCode :: (Applicative f, Choice p) => ErrorCode -> Optic' p f ServiceError ServiceError #
Logging
The exposed logging interface is a primitive Logger
function which the
hooks system calls throughout the request/response process. This allows the
library to output useful information and diagnostics.
The newLogger
function can be used to construct a simple logger which writes
output to a Handle
, but in most production code you should probably consider
using a more robust logging library such as
tinylog or
fast-logger.
Info | Info messages supplied by the user - this level is not emitted by the library. |
Error | Error messages only. |
Debug | Useful debug information + info + error levels. |
Trace | Includes potentially sensitive signing metadata, and non-streaming response bodies. |
Instances
ToByteString LogLevel Source # | |
Defined in Amazonka.Logger toBS :: LogLevel -> ByteString # | |
FromText LogLevel Source # | |
ToText LogLevel Source # | |
Defined in Amazonka.Logger | |
Enum LogLevel Source # | |
Generic LogLevel Source # | |
Show LogLevel Source # | |
Eq LogLevel Source # | |
Ord LogLevel Source # | |
Defined in Amazonka.Logger | |
type Rep LogLevel Source # | |
Defined in Amazonka.Logger type Rep LogLevel = D1 ('MetaData "LogLevel" "Amazonka.Logger" "amazonka-2.0-48plDWnPMAk3PGO79vdSa0" 'False) ((C1 ('MetaCons "Info" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Debug" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Trace" 'PrefixI 'False) (U1 :: Type -> Type))) |
type Logger = LogLevel -> ByteStringBuilder -> IO () Source #
A logging function called by various default hooks to log informational and debug messages.
Constructing a Logger
newLogger :: MonadIO m => LogLevel -> Handle -> m Logger Source #
This is a primitive logger which can be used to log builds to a Handle
.
Note: A more sophisticated logging library such as tinylog or fast-logger should be used in production code.
Re-exported Types
This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.
Instances
FromJSON UTCTime | |
FromJSONKey UTCTime | |
ToJSON UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
ToByteString UTCTime | |
Defined in Amazonka.Data.ByteString toBS :: UTCTime -> ByteString # | |
ToLog UTCTime | |
Defined in Amazonka.Data.Log build :: UTCTime -> ByteStringBuilder # | |
Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime # toConstr :: UTCTime -> Constr # dataTypeOf :: UTCTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) # gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # | |
NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
Eq UTCTime | |
Ord UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime |
may :: Applicative f => ([a] -> f b) -> [a] -> f (Maybe b) #
matchError :: ErrorCode -> Accept -> Acceptor a #
matchStatus :: Int -> Accept -> Acceptor a #
matchNonEmpty :: Bool -> Accept -> Fold (AWSResponse a) b -> Acceptor a #
wait_delay :: Lens' (Wait a) Seconds #
wait_attempts :: Lens' (Wait a) Int #
wait_name :: Lens' (Wait a) ByteString #
type Acceptor a = Request a -> Either Error (ClientResponse (AWSResponse a)) -> Maybe Accept #
Timing and acceptance criteria to check fulfillment of a remote operation.
defaultEndpoint :: Service -> Region -> Endpoint #
Determine the full host address and credential scope
within the specified Region
.
:: Bool | Whether to use HTTPS (ie. SSL). |
-> ByteString | The hostname to connect to. |
-> Int | The port number to connect to. |
-> Service | The service configuration to override. |
-> Service |
A convenience function for overriding the Service
Endpoint
.
See: $sel:endpoint:Service
.
decodeError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Either String ServiceError -> Error #
parseXMLError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error #
parseJSONError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error #
getErrorCode :: Status -> [Header] -> ErrorCode #
getRequestId :: [Header] -> Maybe RequestId #
serviceError :: Abbrev -> Status -> [Header] -> Maybe ErrorCode -> Maybe ErrorMessage -> Maybe RequestId -> ServiceError #
hasCode :: (Applicative f, Choice p) => ErrorCode -> Optic' p f ServiceError ServiceError #
hasStatus :: (Applicative f, Choice p) => Int -> Optic' p f ServiceError ServiceError #
hasService :: (Applicative f, Choice p) => Service -> Optic' p f ServiceError ServiceError #
_HttpStatus :: AsError a => Traversal' a Status #
statusSuccess :: Status -> Bool #
_MatchServiceError :: AsError a => Service -> ErrorCode -> Fold a ServiceError #
Provides a generalised prism for catching a specific service error identified by the opaque service abbreviation and error code.
This can be used if the generated error prisms provided by
Amazonka.ServiceName.Types
do not cover all the thrown error codes.
For example to define a new error prism:
{-# LANGUAGE OverloadedStrings #-} import Amazonka.S3 (ServiceError, s3) _NoSuchBucketPolicy :: AsError a => Fold a ServiceError _NoSuchBucketPolicy = _MatchServiceError s3 "NoSuchBucketPolicy"
With example usage being:
>>>
import Control.Exception.Lens (trying)
>>>
:t trying _NoSuchBucketPolicy
MonadCatch m => m a -> m (Either ServiceError a)
stop :: AWSTruncated a => a -> Bool #
class AWSRequest a => AWSPager a where #
Specify how an AWSRequest
and it's associated Rs
response can
generate a subsequent request, if available.
page :: a -> AWSResponse a -> Maybe a #
class AWSTruncated a where #
Generalise IsTruncated and other optional/required response pagination fields.
Instances
AWSTruncated Bool | |
Defined in Amazonka.Pager | |
AWSTruncated (Maybe Bool) | |
AWSTruncated (Maybe a) | |
Defined in Amazonka.Pager | |
AWSTruncated [a] | |
Defined in Amazonka.Pager | |
AWSTruncated (HashMap k v) | |
Defined in Amazonka.Pager |
toMicroseconds :: Seconds -> Int #
requestUnsigned :: Request a -> Region -> ClientRequest #
Create an unsigned ClientRequest
. You will almost never need to do this.
requestPresign :: Seconds -> Algorithm a #
requestSign :: Algorithm a #
request_body :: Lens' (Request a) RequestBody #
request_headers :: Lens' (Request a) [Header] #
request_query :: Lens' (Request a) QueryString #
request_path :: Lens' (Request a) RawPath #
request_method :: Lens' (Request a) StdMethod #
request_service :: Lens' (Request a) Service #
service_error :: Lens' Service (Status -> [Header] -> ByteStringLazy -> Error) #
signed_signedMeta :: Lens' (Signed a) Meta #
retry_check :: Lens' Retry (ServiceError -> Maybe Text) #
retry_attempts :: Lens' Retry Int #
retry_growth :: Lens' Retry Int #
retry_base :: Lens' Retry Double #
_RequestId :: Iso' RequestId Text #
newErrorCode :: Text -> ErrorCode #
Construct an ErrorCode
.
_ErrorCode :: Iso' ErrorCode Text #
newClientRequest :: Endpoint -> Maybe Seconds -> ClientRequest #
Construct a ClientRequest
using common parameters such as TLS and prevent
throwing errors when receiving erroneous status codes in respones.
type ClientRequest = Request #
A convenience alias to avoid type ambiguity.
type ClientResponse = Response #
A convenience alias encapsulating the common Response
.
type ClientBody = ConduitM () ByteString (ResourceT IO) () #
A convenience alias encapsulating the common Response
body.
Abbreviated service name.
Instances
FromJSON Abbrev | |
ToLog Abbrev | |
Defined in Amazonka.Types build :: Abbrev -> ByteStringBuilder # | |
FromText Abbrev | |
ToText Abbrev | |
Defined in Amazonka.Types | |
FromXML Abbrev | |
IsString Abbrev | |
Defined in Amazonka.Types fromString :: String -> Abbrev # | |
Generic Abbrev | |
Show Abbrev | |
Eq Abbrev | |
Ord Abbrev | |
type Rep Abbrev | |
Defined in Amazonka.Types |
Instances
FromJSON ErrorCode | |
ToLog ErrorCode | |
Defined in Amazonka.Types build :: ErrorCode -> ByteStringBuilder # | |
FromText ErrorCode | |
ToText ErrorCode | |
Defined in Amazonka.Types | |
FromXML ErrorCode | |
IsString ErrorCode | |
Defined in Amazonka.Types fromString :: String -> ErrorCode # | |
Show ErrorCode | |
Eq ErrorCode | |
Ord ErrorCode | |
Defined in Amazonka.Types |
newtype ErrorMessage #
Instances
Instances
FromJSON RequestId | |
ToLog RequestId | |
Defined in Amazonka.Types build :: RequestId -> ByteStringBuilder # | |
FromText RequestId | |
ToText RequestId | |
Defined in Amazonka.Types | |
FromXML RequestId | |
IsString RequestId | |
Defined in Amazonka.Types fromString :: String -> RequestId # | |
Generic RequestId | |
Show RequestId | |
Eq RequestId | |
Ord RequestId | |
Defined in Amazonka.Types | |
type Rep RequestId | |
Defined in Amazonka.Types |
An error type representing errors that can be attributed to this library.
Instances
ToLog Error | |
Defined in Amazonka.Types build :: Error -> ByteStringBuilder # | |
AsError Error | |
Defined in Amazonka.Types | |
Exception Error | |
Defined in Amazonka.Types toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # | |
Generic Error | |
Show Error | |
type Rep Error | |
Defined in Amazonka.Types type Rep Error = D1 ('MetaData "Error" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "TransportError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HttpException)) :+: (C1 ('MetaCons "SerializeError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SerializeError)) :+: C1 ('MetaCons "ServiceError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ServiceError)))) |
data SerializeError #
Instances
data ServiceError #
Instances
A general Amazonka error.
_TransportError :: Prism' a HttpException #
An error occured while communicating over HTTP with a remote service.
_SerializeError :: Prism' a SerializeError #
A serialisation error occured when attempting to deserialise a response.
_ServiceError :: Prism' a ServiceError #
A service specific error returned by the remote service.
Instances
AsError Error | |
Defined in Amazonka.Types | |
AsError SomeException | |
Endpoint | |
|
Instances
Generic Endpoint | |
Show Endpoint | |
Eq Endpoint | |
type Rep Endpoint | |
Defined in Amazonka.Types type Rep Endpoint = D1 ('MetaData "Endpoint" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "Endpoint" 'PrefixI 'True) ((S1 ('MetaSel ('Just "host") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "basePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RawPath)) :*: (S1 ('MetaSel ('Just "secure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "port") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "scope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))) |
Constants and predicates used to create a RetryPolicy
.
Instances
Generic Retry | |
type Rep Retry | |
Defined in Amazonka.Types type Rep Retry = D1 ('MetaData "Retry" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "Exponential" 'PrefixI 'True) ((S1 ('MetaSel ('Just "base") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "growth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "attempts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "check") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ServiceError -> Maybe Text))))) |
Signing algorithm specific metadata.
Instances
ToLog Meta | |
Defined in Amazonka.Types build :: Meta -> ByteStringBuilder # |
A signed ClientRequest
and associated metadata specific
to the signing algorithm, tagged with the initial request type
to be able to obtain the associated response,
.AWSResponse
a
Attributes and functions specific to an AWS service.
Service | |
|
Instances
data S3AddressingStyle #
When to rewrite S3 requests into virtual-hosted style.
Requests to S3 can be rewritten to access buckets by setting the
Host:
header, which allows you to point a CNAME
record at an
Amazon S3 Bucket.
Non-S3 object stores usually do not support this, which is usually the only time you'll need to change this.
See: Virtual hosting of buckets in the Amazon S3 User Guide.
See: Changing the Addressing Style for the corresponding option in Boto 3.
S3AddressingStyleAuto | Rewrite S3 request paths only if they can be expressed as a DNS label. This is the default. |
S3AddressingStylePath | Do not ever rewrite S3 request paths. |
S3AddressingStyleVirtual | Force virtual hosted style rewrites without checking the bucket name. |
Instances
Generic S3AddressingStyle | |
Defined in Amazonka.Types type Rep S3AddressingStyle :: Type -> Type # from :: S3AddressingStyle -> Rep S3AddressingStyle x # to :: Rep S3AddressingStyle x -> S3AddressingStyle # | |
Show S3AddressingStyle | |
Defined in Amazonka.Types showsPrec :: Int -> S3AddressingStyle -> ShowS # show :: S3AddressingStyle -> String # showList :: [S3AddressingStyle] -> ShowS # | |
Eq S3AddressingStyle | |
Defined in Amazonka.Types (==) :: S3AddressingStyle -> S3AddressingStyle -> Bool # (/=) :: S3AddressingStyle -> S3AddressingStyle -> Bool # | |
type Rep S3AddressingStyle | |
Defined in Amazonka.Types type Rep S3AddressingStyle = D1 ('MetaData "S3AddressingStyle" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "S3AddressingStyleAuto" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "S3AddressingStylePath" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "S3AddressingStyleVirtual" 'PrefixI 'False) (U1 :: Type -> Type))) |
An unsigned request.
Instances
Generic (Request a) | |
type Rep (Request a) | |
Defined in Amazonka.Types type Rep (Request a) = D1 ('MetaData "Request" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "Request" 'PrefixI 'True) ((S1 ('MetaSel ('Just "service") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Service) :*: (S1 ('MetaSel ('Just "method") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StdMethod) :*: S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RawPath))) :*: (S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QueryString) :*: (S1 ('MetaSel ('Just "headers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Header]) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RequestBody))))) |
type family AWSResponse a #
The successful, expected response associated with a request.
Instances
type AWSResponse GetRoleCredentials | |
type AWSResponse AssumeRole | |
Defined in Amazonka.STS.AssumeRole | |
type AWSResponse AssumeRoleWithSAML | |
type AWSResponse AssumeRoleWithWebIdentity | |
type AWSResponse DecodeAuthorizationMessage | |
type AWSResponse GetAccessKeyInfo | |
Defined in Amazonka.STS.GetAccessKeyInfo | |
type AWSResponse GetCallerIdentity | |
Defined in Amazonka.STS.GetCallerIdentity | |
type AWSResponse GetFederationToken | |
type AWSResponse GetSessionToken | |
Defined in Amazonka.STS.GetSessionToken |
class AWSRequest a where #
Specify how a request can be de/serialised.
type AWSResponse a #
The successful, expected response associated with a request.
:: MonadResource m | |
=> (ByteStringLazy -> IO ByteStringLazy) | Raw response body hook. |
-> Service | |
-> Proxy a | |
-> ClientResponse ClientBody | |
-> m (Either Error (ClientResponse (AWSResponse a))) |
Instances
An access key ID.
For example: AKIAIOSFODNN7EXAMPLE
Instances
FromJSON AccessKey | |
ToJSON AccessKey | |
Defined in Amazonka.Types | |
ToByteString AccessKey | |
Defined in Amazonka.Types toBS :: AccessKey -> ByteString # | |
ToLog AccessKey | |
Defined in Amazonka.Types build :: AccessKey -> ByteStringBuilder # | |
ToQuery AccessKey | |
Defined in Amazonka.Types toQuery :: AccessKey -> QueryString # | |
FromText AccessKey | |
ToText AccessKey | |
Defined in Amazonka.Types | |
FromXML AccessKey | |
ToXML AccessKey | |
Defined in Amazonka.Types | |
IsString AccessKey | |
Defined in Amazonka.Types fromString :: String -> AccessKey # | |
Generic AccessKey | |
Read AccessKey | |
Show AccessKey | |
NFData AccessKey | |
Defined in Amazonka.Types | |
Eq AccessKey | |
Hashable AccessKey | |
Defined in Amazonka.Types | |
type Rep AccessKey | |
Defined in Amazonka.Types type Rep AccessKey = D1 ('MetaData "AccessKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "AccessKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Secret access key credential.
For example: wJalrXUtnFEMIK7MDENGbPxRfiCYEXAMPLEKE
Instances
FromJSON SecretKey | |
ToJSON SecretKey | |
Defined in Amazonka.Types | |
ToByteString SecretKey | |
Defined in Amazonka.Types toBS :: SecretKey -> ByteString # | |
FromText SecretKey | |
ToText SecretKey | |
Defined in Amazonka.Types | |
FromXML SecretKey | |
ToXML SecretKey | |
Defined in Amazonka.Types | |
IsString SecretKey | |
Defined in Amazonka.Types fromString :: String -> SecretKey # | |
Generic SecretKey | |
NFData SecretKey | |
Defined in Amazonka.Types | |
Eq SecretKey | |
Hashable SecretKey | |
Defined in Amazonka.Types | |
type Rep SecretKey | |
Defined in Amazonka.Types type Rep SecretKey = D1 ('MetaData "SecretKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "SecretKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
newtype SessionToken #
A session token used by STS to temporarily authorise access to an AWS resource.
Instances
The AuthN/AuthZ credential environment.
Instances
FromJSON AuthEnv | |
ToLog AuthEnv | |
Defined in Amazonka.Types build :: AuthEnv -> ByteStringBuilder # | |
FromXML AuthEnv | |
Generic AuthEnv | |
Show AuthEnv | |
NFData AuthEnv | |
Defined in Amazonka.Types | |
Eq AuthEnv | |
type Rep AuthEnv | |
Defined in Amazonka.Types type Rep AuthEnv = D1 ('MetaData "AuthEnv" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "AuthEnv" 'PrefixI 'True) ((S1 ('MetaSel ('Just "accessKeyId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccessKey) :*: S1 ('MetaSel ('Just "secretAccessKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Sensitive SecretKey))) :*: (S1 ('MetaSel ('Just "sessionToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Sensitive SessionToken))) :*: S1 ('MetaSel ('Just "expiration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ISO8601))))) |
An authorisation environment containing AWS credentials, and potentially a reference which can be refreshed out-of-band as temporary credentials expire.
Instances
ToLog Auth | |
Defined in Amazonka.Types build :: Auth -> ByteStringBuilder # |
The available AWS regions.
pattern Ohio :: Region | |
pattern NorthVirginia :: Region | |
pattern NorthCalifornia :: Region | |
pattern Oregon :: Region | |
pattern CapeTown :: Region | |
pattern HongKong :: Region | |
pattern Hyderabad :: Region | |
pattern Jakarta :: Region | |
pattern Melbourne :: Region | |
pattern Mumbai :: Region | |
pattern Osaka :: Region | |
pattern Seoul :: Region | |
pattern Singapore :: Region | |
pattern Sydney :: Region | |
pattern Tokyo :: Region | |
pattern Montreal :: Region | |
pattern Frankfurt :: Region | |
pattern Ireland :: Region | |
pattern London :: Region | |
pattern Milan :: Region | |
pattern Paris :: Region | |
pattern Spain :: Region | |
pattern Stockholm :: Region | |
pattern Zurich :: Region | |
pattern Bahrain :: Region | |
pattern UAE :: Region | |
pattern SaoPaulo :: Region | |
pattern GovCloudEast :: Region | |
pattern GovCloudWest :: Region | |
pattern Beijing :: Region | |
pattern Ningxia :: Region |
Instances
FromJSON Region | |
ToJSON Region | |
Defined in Amazonka.Types | |
ToByteString Region | |
Defined in Amazonka.Types toBS :: Region -> ByteString # | |
ToLog Region | |
Defined in Amazonka.Types build :: Region -> ByteStringBuilder # | |
ToQuery Region | |
Defined in Amazonka.Types toQuery :: Region -> QueryString # | |
FromText Region | |
ToText Region | |
Defined in Amazonka.Types | |
FromXML Region | |
ToXML Region | |
Defined in Amazonka.Types | |
IsString Region | |
Defined in Amazonka.Types fromString :: String -> Region # | |
Generic Region | |
Read Region | |
Show Region | |
NFData Region | |
Defined in Amazonka.Types | |
Eq Region | |
Ord Region | |
Hashable Region | |
Defined in Amazonka.Types | |
type Rep Region | |
Defined in Amazonka.Types |
A numeric value representing seconds.
Instances
ToByteString Seconds | |
Defined in Amazonka.Types toBS :: Seconds -> ByteString # | |
ToLog Seconds | |
Defined in Amazonka.Types build :: Seconds -> ByteStringBuilder # | |
ToQuery Seconds | |
Defined in Amazonka.Types toQuery :: Seconds -> QueryString # | |
FromText Seconds | |
ToText Seconds | |
Defined in Amazonka.Types | |
Enum Seconds | |
Generic Seconds | |
Num Seconds | |
Read Seconds | |
Real Seconds | |
Defined in Amazonka.Types toRational :: Seconds -> Rational # | |
Show Seconds | |
NFData Seconds | |
Defined in Amazonka.Types | |
Eq Seconds | |
Ord Seconds | |
Hashable Seconds | |
Defined in Amazonka.Types | |
type Rep Seconds | |
Defined in Amazonka.Types |
_Base64 :: Iso' Base64 ByteString #
Base64 encoded binary data.
Encoding/decoding is automatically deferred to serialisation and deserialisation respectively.
Instances
FromJSON Base64 | |
ToJSON Base64 | |
Defined in Amazonka.Data.Base64 | |
ToBody Base64 | |
Defined in Amazonka.Data.Base64 toBody :: Base64 -> RequestBody # | |
ToHashedBody Base64 | |
Defined in Amazonka.Data.Base64 toHashed :: Base64 -> HashedBody # | |
ToByteString Base64 | |
Defined in Amazonka.Data.Base64 toBS :: Base64 -> ByteString # | |
ToQuery Base64 | |
Defined in Amazonka.Data.Base64 toQuery :: Base64 -> QueryString # | |
FromText Base64 | |
ToText Base64 | |
Defined in Amazonka.Data.Base64 | |
FromXML Base64 | |
ToXML Base64 | |
Defined in Amazonka.Data.Base64 | |
Generic Base64 | |
Read Base64 | |
Show Base64 | |
NFData Base64 | |
Defined in Amazonka.Data.Base64 | |
Eq Base64 | |
Ord Base64 | |
Hashable Base64 | |
Defined in Amazonka.Data.Base64 | |
type Rep Base64 | |
Defined in Amazonka.Data.Base64 type Rep Base64 = D1 ('MetaData "Base64" "Amazonka.Data.Base64" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Base64" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBase64") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
_Sensitive :: Iso' (Sensitive a) a #
Note: read . show /= isomorphic
Sensitive | |
|
Instances
contentLength :: RequestBody -> Integer #
toRequestBody :: RequestBody -> RequestBody #
isStreaming :: RequestBody -> Bool #
md5Base64 :: RequestBody -> Maybe ByteString #
:: Digest SHA256 | A SHA256 hash of the file contents. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> HashedBody |
Construct a HashedBody
from a Source
, manually specifying the SHA256
hash and file size. It's left up to the caller to calculate these correctly,
otherwise AWS will return signing errors.
See: ToHashedBody
.
:: MonadIO m | |
=> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: hashedFile
, sourceFileRange
.
:: MonadIO m | |
=> FilePath | The file path to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, calculating the SHA256
hash
and file size.
Note: While this function will perform in constant space, it will enumerate the entirety of the file contents twice. Firstly to calculate the SHA256 and lastly to stream the contents to the socket during sending.
See: ToHashedBody
.
sha256Base16 :: HashedBody -> ByteString #
:: forall (m :: Type -> Type). MonadResource m | |
=> ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> ConduitM () ByteString m () |
sourceFileChunks :: forall (m :: Type -> Type). MonadResource m => ChunkSize -> FilePath -> ConduitM () ByteString m () #
:: ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> RequestBody |
Unsafely construct a ChunkedBody
.
This function is marked unsafe because it does nothing to enforce the chunk size.
Typically for conduit IO
functions, it's whatever ByteString's
defaultBufferSize
is, around 32 KB. If the chunk size is less than 8 KB,
the request will error. 64 KB or higher chunk size is recommended for
performance reasons.
Note that it will always create a chunked body even if the request is too small.
See: ToBody
.
:: MonadIO m | |
=> ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m RequestBody |
Construct a ChunkedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: chunkedFile
.
chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RequestBody #
Construct a ChunkedBody
from a FilePath
, where the contents will be
read and signed incrementally in chunks if the target service supports it.
Will intelligently revert to HashedBody
if the file is smaller than the
specified ChunkSize
.
See: ToBody
.
remainderBytes :: ChunkedBody -> Maybe Integer #
fullChunks :: ChunkedBody -> Integer #
fuseChunks :: ChunkedBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ChunkedBody #
chunkedBody_body :: Lens' ChunkedBody (ConduitM () ByteString (ResourceT IO) ()) #
defaultChunkSize :: ChunkSize #
The default chunk size of 128 KB. The minimum chunk size accepted by AWS is 8 KB, unless the entirety of the request is below this threshold.
A chunk size of 64 KB or higher is recommended for performance reasons.
_ChunkSize :: Iso' ChunkSize Int #
sinkBody :: MonadIO m => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a #
Connect a Sink
to a response stream.
fuseStream :: ResponseBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ResponseBody #
_ResponseBody :: Iso' ResponseBody (ConduitM () ByteString (ResourceT IO) ()) #
getFileSize :: MonadIO m => FilePath -> m Integer #
Convenience function for obtaining the size of a file.
newtype ResponseBody #
A streaming, exception safe response body.
newtype
for show/orhpan instance purposes.
ResponseBody | |
|
Instances
Generic ResponseBody | |
Defined in Amazonka.Data.Body type Rep ResponseBody :: Type -> Type # from :: ResponseBody -> Rep ResponseBody x # to :: Rep ResponseBody x -> ResponseBody # | |
Show ResponseBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> ResponseBody -> ShowS # show :: ResponseBody -> String # showList :: [ResponseBody] -> ShowS # | |
type Rep ResponseBody | |
Defined in Amazonka.Data.Body type Rep ResponseBody = D1 ('MetaData "ResponseBody" "Amazonka.Data.Body" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "ResponseBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConduitM () ByteString (ResourceT IO) ())))) |
Specifies the transmitted size of the 'Transfer-Encoding' chunks.
See: defaultChunk
.
Instances
ToLog ChunkSize | |
Defined in Amazonka.Data.Body build :: ChunkSize -> ByteStringBuilder # | |
Enum ChunkSize | |
Defined in Amazonka.Data.Body succ :: ChunkSize -> ChunkSize # pred :: ChunkSize -> ChunkSize # fromEnum :: ChunkSize -> Int # enumFrom :: ChunkSize -> [ChunkSize] # enumFromThen :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromTo :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromThenTo :: ChunkSize -> ChunkSize -> ChunkSize -> [ChunkSize] # | |
Num ChunkSize | |
Integral ChunkSize | |
Defined in Amazonka.Data.Body | |
Real ChunkSize | |
Defined in Amazonka.Data.Body toRational :: ChunkSize -> Rational # | |
Show ChunkSize | |
Eq ChunkSize | |
Ord ChunkSize | |
Defined in Amazonka.Data.Body |
data ChunkedBody #
An opaque request body which will be transmitted via
Transfer-Encoding: chunked
.
Invariant: Only services that support chunked encoding can
accept a ChunkedBody
. (Currently S3.) This is enforced by the type
signatures emitted by the generator.
Instances
ToBody ChunkedBody | |
Defined in Amazonka.Data.Body toBody :: ChunkedBody -> RequestBody # | |
Show ChunkedBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> ChunkedBody -> ShowS # show :: ChunkedBody -> String # showList :: [ChunkedBody] -> ShowS # |
data HashedBody #
An opaque request body containing a SHA256
hash.
HashedStream (Digest SHA256) !Integer (ConduitM () ByteString (ResourceT IO) ()) | |
HashedBytes (Digest SHA256) ByteString |
Instances
ToBody HashedBody | |
Defined in Amazonka.Data.Body toBody :: HashedBody -> RequestBody # | |
ToHashedBody HashedBody | |
Defined in Amazonka.Data.Body toHashed :: HashedBody -> HashedBody # | |
IsString HashedBody | |
Defined in Amazonka.Data.Body fromString :: String -> HashedBody # | |
Show HashedBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> HashedBody -> ShowS # show :: HashedBody -> String # showList :: [HashedBody] -> ShowS # |
data RequestBody #
Invariant: only services that support both standard and
chunked signing expose RequestBody
as a parameter.
Chunked ChunkedBody | Currently S3 only, see |
Hashed HashedBody |
Instances
ToBody RequestBody | |
Defined in Amazonka.Data.Body toBody :: RequestBody -> RequestBody # | |
IsString RequestBody | |
Defined in Amazonka.Data.Body fromString :: String -> RequestBody # | |
Show RequestBody | |
Defined in Amazonka.Data.Body showsPrec :: Int -> RequestBody -> ShowS # show :: RequestBody -> String # showList :: [RequestBody] -> ShowS # |
class ToHashedBody a where #
Anything that can be safely converted to a HashedBody
.
toHashed :: a -> HashedBody #
Convert a value to a hashed request body.
Instances
ToHashedBody Value | |
Defined in Amazonka.Data.Body toHashed :: Value -> HashedBody # | |
ToHashedBody Base64 | |
Defined in Amazonka.Data.Base64 toHashed :: Base64 -> HashedBody # | |
ToHashedBody HashedBody | |
Defined in Amazonka.Data.Body toHashed :: HashedBody -> HashedBody # | |
ToHashedBody QueryString | |
Defined in Amazonka.Data.Body toHashed :: QueryString -> HashedBody # | |
ToHashedBody ByteStringLazy | |
Defined in Amazonka.Data.Body toHashed :: ByteStringLazy -> HashedBody # | |
ToHashedBody TextLazy | |
Defined in Amazonka.Data.Body toHashed :: TextLazy -> HashedBody # | |
ToHashedBody ByteString | |
Defined in Amazonka.Data.Body toHashed :: ByteString -> HashedBody # | |
ToHashedBody Text | |
Defined in Amazonka.Data.Body toHashed :: Text -> HashedBody # | |
ToHashedBody Element | |
Defined in Amazonka.Data.Body toHashed :: Element -> HashedBody # | |
ToHashedBody String | |
Defined in Amazonka.Data.Body toHashed :: String -> HashedBody # | |
ToHashedBody (KeyMap Value) | |
Defined in Amazonka.Data.Body toHashed :: KeyMap Value -> HashedBody # |
Anything that can be converted to a streaming request Body
.
Nothing
toBody :: a -> RequestBody #
Convert a value to a request body.
Instances
buildLines :: [ByteStringBuilder] -> ByteStringBuilder #
Intercalate a list of ByteStringBuilder
s with newlines.
build :: a -> ByteStringBuilder #
Convert a value to a loggable builder.
Instances
ToLog AuthError Source # | |
Defined in Amazonka.Auth.Exception build :: AuthError -> ByteStringBuilder # | |
ToLog |