module Effectful.Zoo.Amazonka.Api.Discover
( discoverAwsEnv,
maybeSetEndpoint,
setAwsEnvEndpointOverride,
setAwsServiceEndpointOverride,
) where
import Amazonka qualified as AWS
import Control.Monad.IO.Class
import Data.Generics.Product.Any
import Data.Text qualified as T
import Data.Text.Encoding qualified as T
import Effectful
import Effectful.Environment
import Effectful.Zoo.Amazonka.Data
import Effectful.Zoo.Core
import HaskellWorks.Prelude
import Lens.Micro
import System.IO qualified as IO
import Text.Read
maybeSetEndpoint :: ()
=> Maybe (String, String)
-> (AwsService -> AwsService)
-> AwsService
-> AwsService
maybeSetEndpoint :: Maybe (String, String)
-> (AwsService -> AwsService) -> AwsService -> AwsService
maybeSetEndpoint = \case
Just (String
host, String
portString) ->
case String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
portString of
Just Int
port -> ((AwsService -> AwsService)
-> (AwsService -> AwsService) -> AwsService -> AwsService
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ByteString -> Int -> AwsService -> AwsService
AWS.setEndpoint Bool
False (Text -> ByteString
T.encodeUtf8 (String -> Text
T.pack String
host)) Int
port)
Maybe Int
Nothing -> (AwsService -> AwsService) -> AwsService -> AwsService
forall a. a -> a
id
Maybe (String, String)
Nothing -> (AwsService -> AwsService) -> AwsService -> AwsService
forall a. a -> a
id
setAwsEnvEndpointOverride :: ByteString -> Int -> Bool -> AwsEnv -> AwsEnv
setAwsEnvEndpointOverride :: ByteString -> Int -> Bool -> AwsEnv -> AwsEnv
setAwsEnvEndpointOverride ByteString
host Int
port Bool
ssl AwsEnv
env = do
AwsEnv
env
AwsEnv -> (AwsEnv -> AwsEnv) -> AwsEnv
forall a b. a -> (a -> b) -> b
& forall {k} (sel :: k) s t a b. HasAny sel s t a b => Lens s t a b
forall (sel :: Symbol) s t a b. HasAny sel s t a b => Lens s t a b
the @"overrides" (((AwsService -> AwsService)
-> Identity (AwsService -> AwsService))
-> AwsEnv -> Identity AwsEnv)
-> (AwsService -> AwsService) -> AwsEnv -> AwsEnv
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ByteString -> Int -> Bool -> AwsService -> AwsService
setAwsServiceEndpointOverride ByteString
host Int
port Bool
ssl
setAwsServiceEndpointOverride :: ByteString -> Int -> Bool -> AwsService -> AwsService
setAwsServiceEndpointOverride :: ByteString -> Int -> Bool -> AwsService -> AwsService
setAwsServiceEndpointOverride ByteString
host Int
port Bool
ssl AwsService
svc =
AwsService
svc AwsService -> (AwsService -> AwsService) -> AwsService
forall a b. a -> (a -> b) -> b
& forall {k} (sel :: k) s t a b. HasAny sel s t a b => Lens s t a b
forall (sel :: Symbol) s t a b. HasAny sel s t a b => Lens s t a b
the @"endpoint" (((Region -> Endpoint) -> Identity (Region -> Endpoint))
-> AwsService -> Identity AwsService)
-> ((Region -> Endpoint) -> Region -> Endpoint)
-> AwsService
-> AwsService
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ \Region -> Endpoint
mkEndpoint Region
region ->
Region -> Endpoint
mkEndpoint Region
region
Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& forall {k} (sel :: k) s t a b. HasAny sel s t a b => Lens s t a b
forall (sel :: Symbol) s t a b. HasAny sel s t a b => Lens s t a b
the @"host" ((ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint)
-> ByteString -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ByteString
host
Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& forall {k} (sel :: k) s t a b. HasAny sel s t a b => Lens s t a b
forall (sel :: Symbol) s t a b. HasAny sel s t a b => Lens s t a b
the @"port" ((Int -> Identity Int) -> Endpoint -> Identity Endpoint)
-> Int -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
port
Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& forall {k} (sel :: k) s t a b. HasAny sel s t a b => Lens s t a b
forall (sel :: Symbol) s t a b. HasAny sel s t a b => Lens s t a b
the @"secure" ((Bool -> Identity Bool) -> Endpoint -> Identity Endpoint)
-> Bool -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
ssl
discoverAwsEnv :: ()
=> r <: Environment
=> r <: IOE
=> Eff r AwsEnv
discoverAwsEnv :: forall (r :: [Effect]).
(r <: Environment, r <: IOE) =>
Eff r AwsEnv
discoverAwsEnv = do
Logger
logger' <- IO Logger -> Eff r Logger
forall a. IO a -> Eff r a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Logger -> Eff r Logger) -> IO Logger -> Eff r Logger
forall a b. (a -> b) -> a -> b
$ LogLevel -> Handle -> IO Logger
forall (m :: * -> *). MonadIO m => LogLevel -> Handle -> m Logger
AWS.newLogger LogLevel
AWS.Debug Handle
IO.stdout
Maybe String
mLocalStackHost <- String -> Eff r (Maybe String)
forall (es :: [Effect]).
(Environment :> es) =>
String -> Eff es (Maybe String)
lookupEnv String
"AWS_LOCALSTACK_HOST"
Maybe String
mLocalStackPort <- String -> Eff r (Maybe String)
forall (es :: [Effect]).
(Environment :> es) =>
String -> Eff es (Maybe String)
lookupEnv String
"AWS_LOCALSTACK_PORT"
Maybe (String, String)
mLocalStackEndpoint <- Maybe (String, String) -> Eff r (Maybe (String, String))
forall a. a -> Eff r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (String, String) -> Eff r (Maybe (String, String)))
-> Maybe (String, String) -> Eff r (Maybe (String, String))
forall a b. (a -> b) -> a -> b
$ (,)
(String -> String -> (String, String))
-> Maybe String -> Maybe (String -> (String, String))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
mLocalStackHost
Maybe (String -> (String, String))
-> Maybe String -> Maybe (String, String)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe String
mLocalStackPort
AwsEnv
discoveredAwsEnv <- IO AwsEnv -> Eff r AwsEnv
forall a. IO a -> Eff r a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AwsEnv -> Eff r AwsEnv) -> IO AwsEnv -> Eff r AwsEnv
forall a b. (a -> b) -> a -> b
$ (EnvNoAuth -> IO AwsEnv) -> IO AwsEnv
forall (m :: * -> *).
MonadIO m =>
(EnvNoAuth -> m AwsEnv) -> m AwsEnv
AWS.newEnv EnvNoAuth -> IO AwsEnv
forall (m :: * -> *) (withAuth :: * -> *).
(MonadCatch m, MonadIO m, Foldable withAuth) =>
Env' withAuth -> m AwsEnv
AWS.discover
pure $ AwsEnv
discoveredAwsEnv
AwsEnv -> (AwsEnv -> AwsEnv) -> AwsEnv
forall a b. a -> (a -> b) -> b
& forall {k} (sel :: k) s t a b. HasAny sel s t a b => Lens s t a b
forall (sel :: Symbol) s t a b. HasAny sel s t a b => Lens s t a b
the @"logger" ((Logger -> Identity Logger) -> AwsEnv -> Identity AwsEnv)
-> Logger -> AwsEnv -> AwsEnv
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Logger
logger'
AwsEnv -> (AwsEnv -> AwsEnv) -> AwsEnv
forall a b. a -> (a -> b) -> b
& forall {k} (sel :: k) s t a b. HasAny sel s t a b => Lens s t a b
forall (sel :: Symbol) s t a b. HasAny sel s t a b => Lens s t a b
the @"overrides" (((AwsService -> AwsService)
-> Identity (AwsService -> AwsService))
-> AwsEnv -> Identity AwsEnv)
-> ((AwsService -> AwsService) -> AwsService -> AwsService)
-> AwsEnv
-> AwsEnv
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Maybe (String, String)
-> (AwsService -> AwsService) -> AwsService -> AwsService
maybeSetEndpoint Maybe (String, String)
mLocalStackEndpoint