Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data Env
- data Region
- data RegionError
- data Debugging
- getRegionFromEnv :: (MonadIO m, MonadThrow m) => ExceptT RegionError m Region
- getDebugging :: MonadIO m => m Debugging
- setDebugging :: Debugging -> Env -> Env
- renderRegionError :: RegionError -> Text
- discoverAWSEnv :: ExceptT RegionError IO Env
- discoverAWSEnvWithRegion :: Region -> IO Env
- discoverAWSEnvRetry :: RetryPolicyM IO -> ExceptT RegionError IO Env
- discoverAWSEnvWithRegionRetry :: RetryPolicyM IO -> Region -> IO Env
- catchAuthError :: AuthError -> IO Bool
- newMismiEnv :: (Applicative m, MonadIO m, MonadCatch m) => Region -> Credentials -> m Env
Documentation
The environment containing the parameters required to make AWS requests.
Instances
MonadAWS AWS | |
Defined in Network.AWS | |
HasEnv Env | |
ToLog Env | |
Defined in Network.AWS.Env |
The available AWS regions.
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 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 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)))))) |
data RegionError Source #
Instances
Eq RegionError Source # | |
Defined in Mismi.Environment (==) :: RegionError -> RegionError -> Bool # (/=) :: RegionError -> RegionError -> Bool # | |
Show RegionError Source # | |
Defined in Mismi.Environment showsPrec :: Int -> RegionError -> ShowS # show :: RegionError -> String # showList :: [RegionError] -> ShowS # |
getRegionFromEnv :: (MonadIO m, MonadThrow m) => ExceptT RegionError m Region Source #
getDebugging :: MonadIO m => m Debugging Source #
renderRegionError :: RegionError -> Text Source #
discoverAWSEnvWithRegionRetry :: RetryPolicyM IO -> Region -> IO Env Source #
newMismiEnv :: (Applicative m, MonadIO m, MonadCatch m) => Region -> Credentials -> m Env Source #