module AWS.Secrets.Fetch where
import AWS.Secrets.Config (SecretsConfig)
import qualified AWS.Secrets.Config as Config
import AWS.Secrets.Name (SecretName, getSecretNameText)
import Control.Applicative (pure)
import Control.Monad.Except (MonadError, throwError)
import Control.Monad.IO.Class (MonadIO)
import qualified Data.Aeson as JSON
import qualified Data.ByteString.Lazy as Lazy
import qualified Data.ByteString.Lazy as Lazy.ByteString
import Data.Either (Either (..))
import Data.Foldable (fold)
import Data.Function (($), (.))
import Data.Int (Int)
import qualified Data.List as List
import Data.Semigroup ((<>))
import Data.String (String)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as Lazy.Text
import qualified Data.Text.Lazy.Builder as Text
import qualified Data.Text.Lazy.Builder as Text.Builder
import qualified System.Exit as Exit
import System.IO (FilePath)
import qualified System.Process.Typed as Process
import Text.Show (Show, show)
fetchSecret ::
forall m result.
(MonadIO m, MonadError Text m, JSON.FromJSON result) =>
SecretsConfig ->
SecretName ->
m result
fetchSecret :: forall (m :: * -> *) result.
(MonadIO m, MonadError Text m, FromJSON result) =>
SecretsConfig -> SecretName -> m result
fetchSecret SecretsConfig
config SecretName
name = do
let secretNameText :: Text
secretNameText :: Text
secretNameText = SecretName -> Text
getSecretNameText SecretName
name
secretNameString :: String
secretNameString :: String
secretNameString = Text -> String
Text.unpack Text
secretNameText
secretNameTextBuilder :: Text.Builder
secretNameTextBuilder :: Builder
secretNameTextBuilder = Text -> Builder
Text.Builder.fromText Text
secretNameText
awsRegionText :: Text
awsRegionText :: Text
awsRegionText = AwsRegion -> Text
Config.getAwsRegionText (SecretsConfig -> AwsRegion
Config.getAwsRegion SecretsConfig
config)
awsRegionString :: String
awsRegionString :: String
awsRegionString = Text -> String
Text.unpack Text
awsRegionText
awsRegionTextBuilder :: Text.Builder
awsRegionTextBuilder :: Builder
awsRegionTextBuilder = Text -> Builder
Text.Builder.fromText Text
awsRegionText
executableFilePath :: FilePath
executableFilePath :: String
executableFilePath = AwsCli -> String
Config.getAwsCliFilePath (SecretsConfig -> AwsCli
Config.getAwsCli SecretsConfig
config)
executableTextBuilder :: Text.Builder
executableTextBuilder :: Builder
executableTextBuilder = String -> Builder
Text.Builder.fromString String
executableFilePath
stringArgs :: [String]
stringArgs :: [String]
stringArgs =
[ String
"secretsmanager",
String
"get-secret-value",
String
"--secret-id",
String
secretNameString,
String
"--region",
String
awsRegionString
]
fullCommandTextBuilder :: Text.Builder
fullCommandTextBuilder :: Builder
fullCommandTextBuilder =
[Builder] -> Builder
unwords
[ Builder
"The exact command executed was:",
forall a. Show a => a -> Builder
showBuilder @[String] (String
executableFilePath forall a. a -> [a] -> [a]
: [String]
stringArgs)
]
descriptionTextBuilder :: Text.Builder
descriptionTextBuilder :: Builder
descriptionTextBuilder =
[Builder] -> Builder
unwords
[ Builder
"AWS command",
Builder -> Builder
quote Builder
executableTextBuilder,
Builder
"to get secret",
Builder -> Builder
quote Builder
secretNameTextBuilder,
Builder
"from region",
Builder -> Builder
quote forall a b. (a -> b) -> a -> b
$ Builder
awsRegionTextBuilder
]
(ExitCode
exitCode :: Exit.ExitCode, ByteString
output :: Lazy.ByteString, ByteString
error :: Lazy.ByteString) <-
forall (m :: * -> *) stdin stdoutIgnored stderrIgnored.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderrIgnored
-> m (ExitCode, ByteString, ByteString)
Process.readProcess (String -> [String] -> ProcessConfig () () ()
Process.proc String
executableFilePath [String]
stringArgs)
let
normalOutputMessage :: Text.Builder
normalOutputMessage :: Builder
normalOutputMessage =
if ByteString -> Bool
Lazy.ByteString.null ByteString
output
then Builder
"It produced no output."
else
[Builder] -> Builder
unwords
[ Builder
"Its output was:",
forall a. Show a => a -> Builder
showBuilder @Lazy.ByteString ByteString
output
]
errorOutputMessage :: Text.Builder
errorOutputMessage :: Builder
errorOutputMessage =
if ByteString -> Bool
Lazy.ByteString.null ByteString
error
then Builder
"It produced no error output."
else
[Builder] -> Builder
unwords
[ Builder
"Its error output was:",
forall a. Show a => a -> Builder
showBuilder @Lazy.ByteString ByteString
error
]
throwParseError :: forall x. String -> m x
throwParseError :: forall x. String -> m x
throwParseError String
parseError =
(forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
render forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
unlines)
[ [Builder] -> Builder
unwords
[ Builder
descriptionTextBuilder,
Builder
"failed to produce valid JSON"
],
Builder
fullCommandTextBuilder,
Builder
normalOutputMessage,
[Builder] -> Builder
unwords
[ Builder
"The output from the parser is:",
String -> Builder
Text.Builder.fromString String
parseError
]
]
throwExitCodeError :: forall x. Int -> m x
throwExitCodeError :: forall x. Int -> m x
throwExitCodeError Int
exitCodeInt =
(forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
render forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
unlines)
[ [Builder] -> Builder
unwords
[ Builder
descriptionTextBuilder,
Builder
"failed with exit code",
Builder -> Builder
quote (forall a. Show a => a -> Builder
showBuilder @Int Int
exitCodeInt)
],
Builder
fullCommandTextBuilder,
Builder
errorOutputMessage
]
case ExitCode
exitCode of
ExitCode
Exit.ExitSuccess -> case forall a. FromJSON a => ByteString -> Either String a
JSON.eitherDecode @result ByteString
output of
Right result
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure result
x
Left String
e -> forall x. String -> m x
throwParseError String
e
Exit.ExitFailure Int
exitCodeInt ->
forall x. Int -> m x
throwExitCodeError Int
exitCodeInt
quote :: Text.Builder -> Text.Builder
quote :: Builder -> Builder
quote Builder
x = Builder
"‘" forall a. Semigroup a => a -> a -> a
<> Builder
x forall a. Semigroup a => a -> a -> a
<> Builder
"’"
unwords :: [Text.Builder] -> Text.Builder
unwords :: [Builder] -> Builder
unwords = forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a] -> [a]
List.intersperse Builder
" "
unlines :: [Text.Builder] -> Text.Builder
unlines :: [Builder] -> Builder
unlines = forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a] -> [a]
List.intersperse Builder
"\n"
showBuilder :: Show a => a -> Text.Builder
showBuilder :: forall a. Show a => a -> Builder
showBuilder = String -> Builder
Text.Builder.fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
render :: Text.Builder -> Text
render :: Builder -> Text
render = Text -> Text
Lazy.Text.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Text.Builder.toLazyText