| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Antiope.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 | |
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.
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 # | |
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.1-ELBIJn8sdXb6y4F0NehmwA" 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)))))) | |