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
- _MatchServiceError :: AsError a => Service -> ErrorCode -> Fold a ServiceError
- statusSuccess :: Status -> Bool
- _HttpStatus :: AsError a => Traversal' a Status
- 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
- serviceError :: Abbrev -> Status -> [Header] -> Maybe ErrorCode -> Maybe ErrorMessage -> Maybe RequestId -> ServiceError
- getRequestId :: [Header] -> Maybe RequestId
- getErrorCode :: Status -> [Header] -> ErrorCode
- parseJSONError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error
- parseXMLError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error
- parseRESTError :: Abbrev -> Status -> [Header] -> a -> Error
- decodeError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Either String ServiceError -> Error
Documentation
_MatchServiceError :: AsError a => Service -> ErrorCode -> Fold a ServiceError Source #
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)
statusSuccess :: Status -> Bool Source #
_HttpStatus :: AsError a => Traversal' a Status Source #
hasService :: (Applicative f, Choice p) => Service -> Optic' p f ServiceError ServiceError Source #
hasStatus :: (Applicative f, Choice p) => Int -> Optic' p f ServiceError ServiceError Source #
hasCode :: (Applicative f, Choice p) => ErrorCode -> Optic' p f ServiceError ServiceError Source #
serviceError :: Abbrev -> Status -> [Header] -> Maybe ErrorCode -> Maybe ErrorMessage -> Maybe RequestId -> ServiceError Source #
parseJSONError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error Source #
parseXMLError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Error Source #
decodeError :: Abbrev -> Status -> [Header] -> ByteStringLazy -> Either String ServiceError -> Error Source #