| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Mismi.Control
Contents
Synopsis
- type AWS = AWST (ResourceT IO)
- data Error
- data AccessKey
- data SecretKey
- data SessionToken
- data Region
- runAWS :: (MonadIO m, MonadCatch m) => Env -> AWS a -> ExceptT Error m a
- runAWST :: Env -> (Error -> e) -> ExceptT e AWS a -> ExceptT e IO a
- runAWSTWith :: (forall b. AWS b -> ExceptT Error IO b) -> (Error -> e) -> ExceptT e AWS a -> ExceptT e IO a
- runAWSTWithRegion :: Region -> (Error -> e) -> ExceptT e AWS a -> ExceptT e IO a
- rawRunAWS :: Env -> AWS a -> IO a
- runAWSWithRegion :: (MonadIO m, MonadCatch m) => Region -> AWS a -> ExceptT Error m a
- newEnvFromCreds :: (Applicative m, MonadIO m, MonadCatch m) => Region -> AccessKey -> SecretKey -> Maybe SessionToken -> m Env
- awsBracket :: AWS a -> (a -> AWS c) -> (a -> AWS b) -> AWS b
- awsBracket_ :: AWS a -> AWS c -> AWS b -> AWS b
- unsafeRunAWS :: Env -> AWS a -> IO a
- renderError :: Error -> Text
- onStatus :: (Status -> Maybe r) -> AWS a -> AWS (Either r a)
- onStatus_ :: r -> (Status -> Maybe r) -> AWS () -> AWS r
- handle404 :: AWS a -> AWS (Maybe a)
- handle403 :: AWS a -> AWS (Maybe a)
- handle301 :: AWS a -> AWS (Maybe a)
- setServiceRetry :: Retry -> AWS a -> AWS a
- setRetry :: Int -> AWS a -> AWS a
- configureRetries :: Int -> Env -> Env
- handleServiceError :: (ServiceError -> Bool) -> (ServiceError -> a) -> AWS a -> AWS a
- withRetries :: (MonadCatch m, MonadMask m, MonadIO m) => Int -> m a -> m a
- withRetriesOf :: (MonadCatch m, MonadMask m, MonadIO m) => RetryPolicyM m -> Int -> m a -> m a
- throwOrRetry :: (MonadCatch m, MonadMask m, MonadIO m) => Int -> SomeException -> RetryStatus -> m RetryStatus
- throwOrRetryOf :: (MonadCatch m, MonadMask m, MonadIO m) => RetryPolicyM m -> Int -> SomeException -> RetryStatus -> m RetryStatus
- timeoutAWS :: Int -> AWS a -> AWS (Maybe a)
Documentation
An error type representing errors that can be attributed to this library.
Instances
| Show Error | |
| ToLog Error | |
Defined in Network.AWS.Types | |
| AsError Error | |
Defined in Network.AWS.Types | |
| Exception Error | |
Defined in Network.AWS.Types Methods toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # | |
An access key ID.
For example: AKIAIOSFODNN7EXAMPLE
Instances
Secret access key credential.
For example: wJalrXUtnFEMIK7MDENGbPxRfiCYEXAMPLEKE
Instances
| Eq SecretKey | |
| Data SecretKey | |
Defined in Network.AWS.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecretKey -> c SecretKey # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecretKey # toConstr :: SecretKey -> Constr # dataTypeOf :: SecretKey -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SecretKey) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecretKey) # gmapT :: (forall b. Data b => b -> b) -> SecretKey -> SecretKey # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecretKey -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecretKey -> r # gmapQ :: (forall d. Data d => d -> u) -> SecretKey -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SecretKey -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecretKey -> m SecretKey # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecretKey -> m SecretKey # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecretKey -> m SecretKey # | |
| IsString SecretKey | |
Defined in Network.AWS.Types Methods fromString :: String -> SecretKey # | |
| Hashable SecretKey | |
Defined in Network.AWS.Types | |
| ToJSON SecretKey | |
Defined in Network.AWS.Types | |
| FromJSON SecretKey | |
| ToText SecretKey | |
Defined in Network.AWS.Types | |
| FromText SecretKey | |
Defined in Network.AWS.Types | |
| ToByteString SecretKey | |
Defined in Network.AWS.Types Methods toBS :: SecretKey -> ByteString # | |
| FromXML SecretKey | |
| ToXML SecretKey | |
Defined in Network.AWS.Types | |
| NFData SecretKey | |
Defined in Network.AWS.Types | |
data SessionToken #
A session token used by STS to temporarily authorise access to an AWS resource.
Instances
The available AWS regions.
Constructors
| NorthVirginia | US East ('us-east-1'). |
| Ohio | US East ('us-east-2'). |
| NorthCalifornia | US West ('us-west-1'). |
| Oregon | US West ('us-west-2'). |
| Montreal | Canada ('ca-central-1'). |
| Tokyo | Asia Pacific ('ap-northeast-1'). |
| Seoul | Asia Pacific ('ap-northeast-2'). |
| Mumbai | Asia Pacific ('ap-south-1'). |
| Singapore | Asia Pacific ('ap-southeast-1'). |
| Sydney | Asia Pacific ('ap-southeast-2'). |
| SaoPaulo | South America ('sa-east-1'). |
| Ireland | EU ('eu-west-1'). |
| London | EU ('eu-west-2'). |
| Frankfurt | EU ('eu-central-1'). |
| GovCloud | US GovCloud ('us-gov-west-1'). |
| GovCloudFIPS | US GovCloud FIPS (S3 Only, 'fips-us-gov-west-1'). |
| Beijing | China ('cn-north-1'). |
Instances
| Bounded Region | |
| Enum Region | |
Defined in Network.AWS.Types | |
| Eq Region | |
| Data Region | |
Defined in Network.AWS.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region # toConstr :: Region -> Constr # dataTypeOf :: Region -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Region) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) # gmapT :: (forall b. Data b => b -> b) -> Region -> Region # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # | |
| Ord Region | |
| Read Region | |
| Show Region | |
| Generic Region | |
| Hashable Region | |
Defined in Network.AWS.Types | |
| ToJSON Region | |
Defined in Network.AWS.Types | |
| FromJSON Region | |
| ToText Region | |
Defined in Network.AWS.Types | |
| FromText Region | |
Defined in Network.AWS.Types | |
| ToByteString Region | |
Defined in Network.AWS.Types Methods toBS :: Region -> ByteString # | |
| ToLog Region | |
Defined in Network.AWS.Types | |
| FromXML Region | |
| ToXML Region | |
Defined in Network.AWS.Types | |
| NFData Region | |
Defined in Network.AWS.Types | |
| type Rep Region | |
Defined in Network.AWS.Types type Rep Region = D1 (MetaData "Region" "Network.AWS.Types" "amazonka-core-1.6.0-GPhbuo1MfRULfKX6qbmh20" False) ((((C1 (MetaCons "NorthVirginia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ohio" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NorthCalifornia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Oregon" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Montreal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Tokyo" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Seoul" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mumbai" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "Singapore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sydney" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SaoPaulo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ireland" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "London" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Frankfurt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GovCloud" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GovCloudFIPS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Beijing" PrefixI False) (U1 :: Type -> Type)))))) | |
runAWSTWith :: (forall b. AWS b -> ExceptT Error IO b) -> (Error -> e) -> ExceptT e AWS a -> ExceptT e IO a Source #
runAWSWithRegion :: (MonadIO m, MonadCatch m) => Region -> AWS a -> ExceptT Error m a Source #
newEnvFromCreds :: (Applicative m, MonadIO m, MonadCatch m) => Region -> AccessKey -> SecretKey -> Maybe SessionToken -> m Env Source #
renderError :: Error -> Text Source #
onStatus :: (Status -> Maybe r) -> AWS a -> AWS (Either r a) Source #
Return a result code depending on the HTTP status
onStatus_ :: r -> (Status -> Maybe r) -> AWS () -> AWS r Source #
Return a result code depending on the HTTP status for an AWS action returning no value
handleServiceError :: (ServiceError -> Bool) -> (ServiceError -> a) -> AWS a -> AWS a Source #
withRetries :: (MonadCatch m, MonadMask m, MonadIO m) => Int -> m a -> m a Source #
withRetriesOf :: (MonadCatch m, MonadMask m, MonadIO m) => RetryPolicyM m -> Int -> m a -> m a Source #
throwOrRetry :: (MonadCatch m, MonadMask m, MonadIO m) => Int -> SomeException -> RetryStatus -> m RetryStatus Source #
throwOrRetryOf :: (MonadCatch m, MonadMask m, MonadIO m) => RetryPolicyM m -> Int -> SomeException -> RetryStatus -> m RetryStatus Source #