module Amazonka.Auth.Keys where
import Amazonka.Auth.Exception (_MissingEnvError)
import Amazonka.Core.Lens.Internal (throwingM)
import Amazonka.Data
import Amazonka.Env (Env, Env' (..))
import Amazonka.Prelude
import Amazonka.Types
import Control.Monad.Trans.Maybe (MaybeT (..))
import qualified Data.ByteString.Char8 as BS8
import Data.Foldable (asum)
import qualified System.Environment as Environment
fromKeys :: AccessKey -> SecretKey -> Env' withAuth -> Env
fromKeys :: forall (withAuth :: * -> *).
AccessKey -> SecretKey -> Env' withAuth -> Env
fromKeys AccessKey
a SecretKey
s Env' withAuth
env =
Env' withAuth
env {$sel:auth:Env :: Identity Auth
auth = forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. AuthEnv -> Auth
Auth forall a b. (a -> b) -> a -> b
$ AccessKey
-> Sensitive SecretKey
-> Maybe (Sensitive SessionToken)
-> Maybe ISO8601
-> AuthEnv
AuthEnv AccessKey
a (forall a. a -> Sensitive a
Sensitive SecretKey
s) forall a. Maybe a
Nothing forall a. Maybe a
Nothing}
fromSession ::
AccessKey -> SecretKey -> SessionToken -> Env' withAuth -> Env
fromSession :: forall (withAuth :: * -> *).
AccessKey -> SecretKey -> SessionToken -> Env' withAuth -> Env
fromSession AccessKey
a SecretKey
s SessionToken
t Env' withAuth
env =
Env' withAuth
env
{ $sel:auth:Env :: Identity Auth
auth =
forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. AuthEnv -> Auth
Auth forall a b. (a -> b) -> a -> b
$
AccessKey
-> Sensitive SecretKey
-> Maybe (Sensitive SessionToken)
-> Maybe ISO8601
-> AuthEnv
AuthEnv AccessKey
a (forall a. a -> Sensitive a
Sensitive SecretKey
s) (forall a. a -> Maybe a
Just (forall a. a -> Sensitive a
Sensitive SessionToken
t)) forall a. Maybe a
Nothing
}
fromTemporarySession ::
AccessKey ->
SecretKey ->
SessionToken ->
UTCTime ->
Env' withAuth ->
Env
fromTemporarySession :: forall (withAuth :: * -> *).
AccessKey
-> SecretKey -> SessionToken -> UTCTime -> Env' withAuth -> Env
fromTemporarySession AccessKey
a SecretKey
s SessionToken
t UTCTime
e Env' withAuth
env =
Env' withAuth
env
{ $sel:auth:Env :: Identity Auth
auth =
forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. AuthEnv -> Auth
Auth forall a b. (a -> b) -> a -> b
$
AccessKey
-> Sensitive SecretKey
-> Maybe (Sensitive SessionToken)
-> Maybe ISO8601
-> AuthEnv
AuthEnv AccessKey
a (forall a. a -> Sensitive a
Sensitive SecretKey
s) (forall a. a -> Maybe a
Just (forall a. a -> Sensitive a
Sensitive SessionToken
t)) (forall a. a -> Maybe a
Just (forall (a :: Format). UTCTime -> Time a
Time UTCTime
e))
}
fromKeysEnv :: MonadIO m => Env' withAuth -> m Env
fromKeysEnv :: forall (m :: * -> *) (withAuth :: * -> *).
MonadIO m =>
Env' withAuth -> m Env
fromKeysEnv Env' withAuth
env = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Auth
keys <- AuthEnv -> Auth
Auth forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO AuthEnv
lookupKeys
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Env' withAuth
env {$sel:auth:Env :: Identity Auth
auth = forall a. a -> Identity a
Identity Auth
keys}
where
lookupKeys :: IO AuthEnv
lookupKeys =
AccessKey
-> Sensitive SecretKey
-> Maybe (Sensitive SessionToken)
-> Maybe ISO8601
-> AuthEnv
AuthEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO AccessKey
lookupAccessKey
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO (Sensitive SecretKey)
lookupSecretKey
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO (Maybe (Sensitive SessionToken))
lookupSessionToken
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
lookupAccessKey :: IO AccessKey
lookupAccessKey :: IO AccessKey
lookupAccessKey = do
Maybe String
mVal <-
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum
[ forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (String -> IO (Maybe String)
nonEmptyEnv String
"AWS_ACCESS_KEY_ID"),
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (String -> IO (Maybe String)
nonEmptyEnv String
"AWS_ACCESS_KEY")
]
case Maybe String
mVal of
Maybe String
Nothing ->
forall (m :: * -> *) b r.
MonadThrow m =>
AReview SomeException b -> b -> m r
throwingM
forall a. AsAuthError a => Prism' a Text
_MissingEnvError
Text
"Unable to read access key from AWS_ACCESS_KEY_ID (or AWS_ACCESS_KEY)"
Just String
v -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> AccessKey
AccessKey forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS8.pack String
v
lookupSecretKey :: IO (Sensitive SecretKey)
lookupSecretKey :: IO (Sensitive SecretKey)
lookupSecretKey = do
Maybe String
mVal <-
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum
[ forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (String -> IO (Maybe String)
nonEmptyEnv String
"AWS_SECRET_ACCESS_KEY"),
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (String -> IO (Maybe String)
nonEmptyEnv String
"AWS_SECRET_KEY")
]
case Maybe String
mVal of
Maybe String
Nothing ->
forall (m :: * -> *) b r.
MonadThrow m =>
AReview SomeException b -> b -> m r
throwingM
forall a. AsAuthError a => Prism' a Text
_MissingEnvError
Text
"Unable to read secret key from AWS_SECRET_ACCESS_KEY (or AWS_SECRET_KEY)"
Just String
v -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Sensitive a
Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> SecretKey
SecretKey forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS8.pack String
v
lookupSessionToken :: IO (Maybe (Sensitive SessionToken))
lookupSessionToken :: IO (Maybe (Sensitive SessionToken))
lookupSessionToken =
String -> IO (Maybe String)
nonEmptyEnv String
"AWS_SESSION_TOKEN"
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> Sensitive a
Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> SessionToken
SessionToken forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS8.pack)
nonEmptyEnv :: String -> IO (Maybe String)
nonEmptyEnv :: String -> IO (Maybe String)
nonEmptyEnv String
var =
String -> IO (Maybe String)
Environment.lookupEnv String
var 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
v -> forall a. a -> Maybe a
Just String
v