| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Antiope.Core
Contents
Synopsis
- data Text
- class ToText a where
- class FromText a where
- fromText :: FromText a => Text -> Either String a
- data Env
- class HasEnv a where
- runAWS :: (MonadResource m, HasEnv r) => r -> AWS a -> m a
- send :: (MonadAWS m, AWSRequest a) => a -> m (Rs a)
- runResourceT :: MonadUnliftIO m => ResourceT m a -> m a
- liftAWS :: MonadAWS m => AWS a -> m a
- sinkMD5 :: Monad m => ConduitM ByteString o m (Digest MD5)
- sinkSHA256 :: Monad m => ConduitM ByteString o m (Digest SHA256)
- type AWS = AWST (ResourceT IO)
- catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r
- data Error
- newtype ErrorCode = ErrorCode Text
- errorCode :: Text -> ErrorCode
- data Region
- data LogLevel
- runAws :: (MonadResource m, HasEnv r) => r -> AWS a -> m a
- runAwsThe :: forall m r e s a. (MonadUnliftIO m, MonadReader r m, HasAny s r r e e, HasEnv e) => AWS a -> m a
- runAwsTyped :: forall m r a. (MonadUnliftIO m, MonadReader r m, HasType Env r) => AWS a -> m a
- runResAws :: (MonadUnliftIO m, HasEnv r) => r -> AWS a -> m a
- runResAwsThe :: forall m r e s a. (MonadResource m, MonadReader r m, HasAny s r r e e, HasEnv e) => AWS a -> m a
- runResAwsTyped :: forall m r a. (MonadResource m, MonadReader r m, HasType Env r) => AWS a -> m a
Documentation
A space efficient, packed, unboxed Unicode text type.
Instances
Minimal complete definition
Instances
Minimal complete definition
Instances
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 | |
Minimal complete definition
Methods
environment :: Lens' a Env #
The current region.
The function used to output log messages.
envRetryCheck :: Lens' a (Int -> HttpException -> Bool) #
The function used to determine if an HttpException should be retried.
envOverride :: Lens' a (Dual (Endo Service)) #
The currently applied overrides to all Service configuration.
envManager :: Lens' a Manager #
The Manager used to create and manage open HTTP connections.
The credentials used to sign requests for authentication with AWS.
envEC2 :: Getter a (IORef (Maybe Bool)) #
A memoised predicate for whether the underlying host is an EC2 instance.
runAWS :: (MonadResource m, HasEnv r) => r -> AWS a -> m a #
Run the AWS monad. Any outstanding HTTP responses' ResumableSource will
be closed when the ResourceT computation is unwrapped with runResourceT.
Throws Error, which will include HTTPExceptions, serialisation errors,
or any particular errors returned by the respective AWS service.
See: runAWST, runResourceT.
send :: (MonadAWS m, AWSRequest a) => a -> m (Rs a) #
Send a request, returning the associated response if successful.
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
sinkSHA256 :: Monad m => ConduitM ByteString o m (Digest SHA256) #
catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r #
Catch exceptions that match a given Prism (or any Fold, really).
>>>catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught""caught"
catching::MonadCatchm =>Prism'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>Lens'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>Traversal'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>Iso'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>GetterSomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>FoldSomeExceptiona -> m r -> (a -> m r) -> m r
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 # | |
Instances
| Eq ErrorCode | |
| Ord ErrorCode | |
| Show ErrorCode | |
| IsString ErrorCode | |
Defined in Network.AWS.Types Methods fromString :: String -> ErrorCode # | |
| FromJSON ErrorCode | |
| ToText ErrorCode | |
Defined in Network.AWS.Types | |
| FromText ErrorCode | |
Defined in Network.AWS.Types | |
| ToLog ErrorCode | |
Defined in Network.AWS.Types | |
| FromXML ErrorCode | |
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-5PkStfPD0HEBLMpWPMnHIe" False) ((((C1 (MetaCons "NorthVirginia" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Ohio" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "NorthCalifornia" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Oregon" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Montreal" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Tokyo" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Seoul" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Mumbai" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "Singapore" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Sydney" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "SaoPaulo" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Ireland" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "London" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Frankfurt" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "GovCloud" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "GovCloudFIPS" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Beijing" PrefixI False) (U1 :: * -> *)))))) | |
Constructors
| 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
| Enum LogLevel | |
Defined in Network.AWS.Types | |
| Eq LogLevel | |
| Data LogLevel | |
Defined in Network.AWS.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LogLevel -> c LogLevel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LogLevel # toConstr :: LogLevel -> Constr # dataTypeOf :: LogLevel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LogLevel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LogLevel) # gmapT :: (forall b. Data b => b -> b) -> LogLevel -> LogLevel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LogLevel -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LogLevel -> r # gmapQ :: (forall d. Data d => d -> u) -> LogLevel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LogLevel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel # | |
| Ord LogLevel | |
Defined in Network.AWS.Types | |
| Show LogLevel | |
| ToText LogLevel | |
Defined in Network.AWS.Types | |
| FromText LogLevel | |
Defined in Network.AWS.Types | |
| ToByteString LogLevel | |
Defined in Network.AWS.Types Methods toBS :: LogLevel -> ByteString # | |
runAwsThe :: forall m r e s a. (MonadUnliftIO m, MonadReader r m, HasAny s r r e e, HasEnv e) => AWS a -> m a Source #
runAwsTyped :: forall m r a. (MonadUnliftIO m, MonadReader r m, HasType Env r) => AWS a -> m a Source #
runResAwsThe :: forall m r e s a. (MonadResource m, MonadReader r m, HasAny s r r e e, HasEnv e) => AWS a -> m a Source #
runResAwsTyped :: forall m r a. (MonadResource m, MonadReader r m, HasType Env r) => AWS a -> m a Source #