module Amazonka.Env
(
newEnv,
newEnvFromManager,
newEnvNoAuth,
newEnvNoAuthFromManager,
Env' (..),
Env,
EnvNoAuth,
authMaybe,
lookupRegion,
env_region,
env_logger,
env_hooks,
env_retryCheck,
env_overrides,
env_manager,
env_auth,
overrideService,
configureService,
globalTimeout,
once,
retryConnectionFailure,
)
where
import Amazonka.Core.Lens.Internal (Lens)
import Amazonka.Env.Hooks (Hooks, addLoggingHooks, noHooks)
import Amazonka.Logger (Logger)
import Amazonka.Prelude
import Amazonka.Types hiding (timeout)
import qualified Amazonka.Types as Service (Service (..))
import qualified Data.Function as Function
import qualified Data.Text as Text
import qualified Network.HTTP.Client as Client
import qualified Network.HTTP.Conduit as Client.Conduit
import System.Environment as Environment
type Env = Env' Identity
type EnvNoAuth = Env' Proxy
data Env' withAuth = Env
{ forall (withAuth :: * -> *). Env' withAuth -> Region
region :: Region,
forall (withAuth :: * -> *). Env' withAuth -> Logger
logger :: Logger,
forall (withAuth :: * -> *). Env' withAuth -> Hooks
hooks :: ~Hooks,
forall (withAuth :: * -> *).
Env' withAuth -> Int -> HttpException -> Bool
retryCheck :: Int -> Client.HttpException -> Bool,
forall (withAuth :: * -> *). Env' withAuth -> Service -> Service
overrides :: Service -> Service,
forall (withAuth :: * -> *). Env' withAuth -> Manager
manager :: Client.Manager,
forall (withAuth :: * -> *). Env' withAuth -> withAuth Auth
auth :: withAuth Auth
}
deriving stock (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (withAuth :: * -> *) x.
Rep (Env' withAuth) x -> Env' withAuth
forall (withAuth :: * -> *) x.
Env' withAuth -> Rep (Env' withAuth) x
$cto :: forall (withAuth :: * -> *) x.
Rep (Env' withAuth) x -> Env' withAuth
$cfrom :: forall (withAuth :: * -> *) x.
Env' withAuth -> Rep (Env' withAuth) x
Generic)
{-# INLINE env_region #-}
env_region :: Lens' (Env' withAuth) Region
env_region :: forall (withAuth :: * -> *). Lens' (Env' withAuth) Region
env_region Region -> f Region
f e :: Env' withAuth
e@Env {Region
region :: Region
$sel:region:Env :: forall (withAuth :: * -> *). Env' withAuth -> Region
region} = Region -> f Region
f Region
region forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Region
region' -> Env' withAuth
e {$sel:region:Env :: Region
region = Region
region'}
{-# INLINE env_logger #-}
env_logger :: Lens' (Env' withAuth) Logger
env_logger :: forall (withAuth :: * -> *). Lens' (Env' withAuth) Logger
env_logger Logger -> f Logger
f e :: Env' withAuth
e@Env {Logger
logger :: Logger
$sel:logger:Env :: forall (withAuth :: * -> *). Env' withAuth -> Logger
logger} = Logger -> f Logger
f Logger
logger forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Logger
logger' -> Env' withAuth
e {$sel:logger:Env :: Logger
logger = Logger
logger'}
{-# INLINE env_hooks #-}
env_hooks :: Lens' (Env' withAuth) Hooks
env_hooks :: forall (withAuth :: * -> *). Lens' (Env' withAuth) Hooks
env_hooks Hooks -> f Hooks
f e :: Env' withAuth
e@Env {Hooks
hooks :: Hooks
$sel:hooks:Env :: forall (withAuth :: * -> *). Env' withAuth -> Hooks
hooks} = Hooks -> f Hooks
f Hooks
hooks forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Hooks
hooks' -> Env' withAuth
e {$sel:hooks:Env :: Hooks
hooks = Hooks
hooks'}
{-# INLINE env_retryCheck #-}
env_retryCheck :: Lens' (Env' withAuth) (Int -> Client.HttpException -> Bool)
env_retryCheck :: forall (withAuth :: * -> *).
Lens' (Env' withAuth) (Int -> HttpException -> Bool)
env_retryCheck (Int -> HttpException -> Bool) -> f (Int -> HttpException -> Bool)
f e :: Env' withAuth
e@Env {Int -> HttpException -> Bool
retryCheck :: Int -> HttpException -> Bool
$sel:retryCheck:Env :: forall (withAuth :: * -> *).
Env' withAuth -> Int -> HttpException -> Bool
retryCheck} = (Int -> HttpException -> Bool) -> f (Int -> HttpException -> Bool)
f Int -> HttpException -> Bool
retryCheck forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Int -> HttpException -> Bool
retryCheck' -> Env' withAuth
e {$sel:retryCheck:Env :: Int -> HttpException -> Bool
retryCheck = Int -> HttpException -> Bool
retryCheck'}
{-# INLINE env_overrides #-}
env_overrides :: Lens' (Env' withAuth) (Service -> Service)
env_overrides :: forall (withAuth :: * -> *).
Lens' (Env' withAuth) (Service -> Service)
env_overrides (Service -> Service) -> f (Service -> Service)
f e :: Env' withAuth
e@Env {Service -> Service
overrides :: Service -> Service
$sel:overrides:Env :: forall (withAuth :: * -> *). Env' withAuth -> Service -> Service
overrides} = (Service -> Service) -> f (Service -> Service)
f Service -> Service
overrides forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Service -> Service
overrides' -> Env' withAuth
e {$sel:overrides:Env :: Service -> Service
overrides = Service -> Service
overrides'}
{-# INLINE env_manager #-}
env_manager :: Lens' (Env' withAuth) Client.Manager
env_manager :: forall (withAuth :: * -> *). Lens' (Env' withAuth) Manager
env_manager Manager -> f Manager
f e :: Env' withAuth
e@Env {Manager
manager :: Manager
$sel:manager:Env :: forall (withAuth :: * -> *). Env' withAuth -> Manager
manager} = Manager -> f Manager
f Manager
manager forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Manager
manager' -> Env' withAuth
e {$sel:manager:Env :: Manager
manager = Manager
manager'}
{-# INLINE env_auth #-}
env_auth :: Lens (Env' withAuth) (Env' withAuth') (withAuth Auth) (withAuth' Auth)
env_auth :: forall (withAuth :: * -> *) (withAuth' :: * -> *).
Lens
(Env' withAuth) (Env' withAuth') (withAuth Auth) (withAuth' Auth)
env_auth withAuth Auth -> f (withAuth' Auth)
f e :: Env' withAuth
e@Env {withAuth Auth
auth :: withAuth Auth
$sel:auth:Env :: forall (withAuth :: * -> *). Env' withAuth -> withAuth Auth
auth} = withAuth Auth -> f (withAuth' Auth)
f withAuth Auth
auth forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \withAuth' Auth
auth' -> Env' withAuth
e {$sel:auth:Env :: withAuth' Auth
auth = withAuth' Auth
auth'}
newEnv ::
MonadIO m =>
(EnvNoAuth -> m Env) ->
m Env
newEnv :: forall (m :: * -> *). MonadIO m => (EnvNoAuth -> m Env) -> m Env
newEnv = (forall (m :: * -> *). MonadIO m => m EnvNoAuth
newEnvNoAuth forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=)
newEnvFromManager ::
MonadIO m =>
Client.Manager ->
(EnvNoAuth -> m Env) ->
m Env
newEnvFromManager :: forall (m :: * -> *).
MonadIO m =>
Manager -> (EnvNoAuth -> m Env) -> m Env
newEnvFromManager Manager
manager = (forall (m :: * -> *). MonadIO m => Manager -> m EnvNoAuth
newEnvNoAuthFromManager Manager
manager forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=)
newEnvNoAuth :: MonadIO m => m EnvNoAuth
newEnvNoAuth :: forall (m :: * -> *). MonadIO m => m EnvNoAuth
newEnvNoAuth =
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ManagerSettings -> IO Manager
Client.newManager ManagerSettings
Client.Conduit.tlsManagerSettings)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadIO m => Manager -> m EnvNoAuth
newEnvNoAuthFromManager
newEnvNoAuthFromManager :: MonadIO m => Client.Manager -> m EnvNoAuth
newEnvNoAuthFromManager :: forall (m :: * -> *). MonadIO m => Manager -> m EnvNoAuth
newEnvNoAuthFromManager Manager
manager = do
Maybe Region
mRegion <- forall (m :: * -> *). MonadIO m => m (Maybe Region)
lookupRegion
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Env
{ $sel:region:Env :: Region
region = forall a. a -> Maybe a -> a
fromMaybe Region
NorthVirginia Maybe Region
mRegion,
$sel:logger:Env :: Logger
logger = \LogLevel
_ ByteStringBuilder
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (),
$sel:hooks:Env :: Hooks
hooks = Hooks -> Hooks
addLoggingHooks Hooks
noHooks,
$sel:retryCheck:Env :: Int -> HttpException -> Bool
retryCheck = Int -> Int -> HttpException -> Bool
retryConnectionFailure Int
3,
$sel:overrides:Env :: Service -> Service
overrides = forall a. a -> a
id,
Manager
manager :: Manager
$sel:manager:Env :: Manager
manager,
$sel:auth:Env :: Proxy Auth
auth = forall {k} (t :: k). Proxy t
Proxy
}
authMaybe :: Foldable withAuth => Env' withAuth -> Maybe Auth
authMaybe :: forall (withAuth :: * -> *).
Foldable withAuth =>
Env' withAuth -> Maybe Auth
authMaybe = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just) forall a. Maybe a
Nothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (withAuth :: * -> *). Env' withAuth -> withAuth Auth
auth
lookupRegion :: MonadIO m => m (Maybe Region)
lookupRegion :: forall (m :: * -> *). MonadIO m => m (Maybe Region)
lookupRegion =
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
String -> IO (Maybe String)
Environment.lookupEnv String
"AWS_REGION" forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
Maybe String
Nothing -> forall a. Maybe a
Nothing
Just String
"" -> forall a. Maybe a
Nothing
Just String
t -> forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Region
Region' forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
t
retryConnectionFailure :: Int -> Int -> Client.HttpException -> Bool
retryConnectionFailure :: Int -> Int -> HttpException -> Bool
retryConnectionFailure Int
limit Int
n = \case
Client.InvalidUrlException {} -> Bool
False
Client.HttpExceptionRequest Request
_ HttpExceptionContent
ex
| Int
n forall a. Ord a => a -> a -> Bool
>= Int
limit -> Bool
False
| Bool
otherwise ->
case HttpExceptionContent
ex of
HttpExceptionContent
Client.NoResponseDataReceived -> Bool
True
HttpExceptionContent
Client.ConnectionTimeout -> Bool
True
HttpExceptionContent
Client.ConnectionClosed -> Bool
True
Client.ConnectionFailure {} -> Bool
True
Client.InternalException {} -> Bool
True
HttpExceptionContent
_other -> Bool
False
overrideService :: (Service -> Service) -> Env' withAuth -> Env' withAuth
overrideService :: forall (withAuth :: * -> *).
(Service -> Service) -> Env' withAuth -> Env' withAuth
overrideService Service -> Service
f Env' withAuth
env = Env' withAuth
env {$sel:overrides:Env :: Service -> Service
overrides = Service -> Service
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (withAuth :: * -> *). Env' withAuth -> Service -> Service
overrides Env' withAuth
env}
configureService :: Service -> Env' withAuth -> Env' withAuth
configureService :: forall (withAuth :: * -> *).
Service -> Env' withAuth -> Env' withAuth
configureService Service
s = forall (withAuth :: * -> *).
(Service -> Service) -> Env' withAuth -> Env' withAuth
overrideService Service -> Service
f
where
f :: Service -> Service
f Service
x
| forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
Function.on forall a. Eq a => a -> a -> Bool
(==) Service -> Abbrev
Service.abbrev Service
s Service
x = Service
s
| Bool
otherwise = Service
x
globalTimeout :: Seconds -> Env' withAuth -> Env' withAuth
globalTimeout :: forall (withAuth :: * -> *).
Seconds -> Env' withAuth -> Env' withAuth
globalTimeout Seconds
n = forall (withAuth :: * -> *).
(Service -> Service) -> Env' withAuth -> Env' withAuth
overrideService forall a b. (a -> b) -> a -> b
$ \Service
s -> Service
s {$sel:timeout:Service :: Maybe Seconds
Service.timeout = forall a. a -> Maybe a
Just Seconds
n}
once :: Env' withAuth -> Env' withAuth
once :: forall (withAuth :: * -> *). Env' withAuth -> Env' withAuth
once = forall (withAuth :: * -> *).
(Service -> Service) -> Env' withAuth -> Env' withAuth
overrideService forall a b. (a -> b) -> a -> b
$ \s :: Service
s@Service {Retry
$sel:retry:Service :: Service -> Retry
retry :: Retry
retry} -> Service
s {$sel:retry:Service :: Retry
retry = Retry
retry {$sel:attempts:Exponential :: Int
attempts = Int
0}}