{-# LANGUAGE MultiWayIf #-}
module Stackctl.AWS.Lambda
( LambdaInvokeResult (..)
, LambdaError (..)
, logLambdaInvocationResult
, isLambdaInvocationSuccess
, awsLambdaInvoke
) where
import Stackctl.Prelude hiding (trace)
import Amazonka.Lambda.Invoke
import Data.Aeson
import qualified Data.ByteString.Lazy as BSL
import Stackctl.AWS.Core
data LambdaInvokeResult
= LambdaInvokeSuccess ByteString
| LambdaInvokeError LambdaError (Maybe Text)
| LambdaInvokeFailure Int (Maybe Text)
deriving stock (Int -> LambdaInvokeResult -> ShowS
[LambdaInvokeResult] -> ShowS
LambdaInvokeResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LambdaInvokeResult] -> ShowS
$cshowList :: [LambdaInvokeResult] -> ShowS
show :: LambdaInvokeResult -> String
$cshow :: LambdaInvokeResult -> String
showsPrec :: Int -> LambdaInvokeResult -> ShowS
$cshowsPrec :: Int -> LambdaInvokeResult -> ShowS
Show)
logLambdaInvocationResult :: MonadLogger m => LambdaInvokeResult -> m ()
logLambdaInvocationResult :: forall (m :: * -> *). MonadLogger m => LambdaInvokeResult -> m ()
logLambdaInvocationResult = \case
LambdaInvokeSuccess ByteString
bs -> do
let meta :: [SeriesElem]
meta = case forall a. FromJSON a => ByteString -> Maybe a
decode @Value forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BSL.fromStrict ByteString
bs of
Maybe Value
Nothing -> [Key
"response" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ByteString -> Text
decodeUtf8 ByteString
bs]
Just Value
response -> [Key
"response" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value
response]
forall (m :: * -> *).
(HasCallStack, MonadLogger m) =>
Message -> m ()
logInfo forall a b. (a -> b) -> a -> b
$ Text
"LambdaInvokeSuccess" Text -> [SeriesElem] -> Message
:# [SeriesElem]
meta
LambdaInvokeError LambdaError {[Text]
Text
trace :: LambdaError -> [Text]
errorMessage :: LambdaError -> Text
errorType :: LambdaError -> Text
trace :: [Text]
errorMessage :: Text
errorType :: Text
..} Maybe Text
mFunctionError ->
forall (m :: * -> *).
(HasCallStack, MonadLogger m) =>
Message -> m ()
logError
forall a b. (a -> b) -> a -> b
$ (Text -> [SeriesElem] -> Message
:# [])
forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ Text
"LambdaInvokeError"
, Text
"\n errorType: " forall a. Semigroup a => a -> a -> a
<> Text
errorType
, Text
"\n errorMessage: " forall a. Semigroup a => a -> a -> a
<> Text
errorMessage
, Text
"\n trace: "
, forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (Text
"\n " forall a. Semigroup a => a -> a -> a
<>) [Text]
trace
, Text
"\n FunctionError: " forall a. Semigroup a => a -> a -> a
<> forall a. a -> Maybe a -> a
fromMaybe Text
"none" Maybe Text
mFunctionError
]
LambdaInvokeFailure Int
status Maybe Text
mFunctionError ->
forall (m :: * -> *).
(HasCallStack, MonadLogger m) =>
Message -> m ()
logError
forall a b. (a -> b) -> a -> b
$ (Text -> [SeriesElem] -> Message
:# [])
forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ Text
"LambdaInvokeFailure"
, Text
"\n StatusCode: " forall a. Semigroup a => a -> a -> a
<> String -> Text
pack (forall a. Show a => a -> String
show Int
status)
, Text
"\n FunctionError: " forall a. Semigroup a => a -> a -> a
<> forall a. a -> Maybe a -> a
fromMaybe Text
"none" Maybe Text
mFunctionError
]
isLambdaInvocationSuccess :: LambdaInvokeResult -> Bool
isLambdaInvocationSuccess :: LambdaInvokeResult -> Bool
isLambdaInvocationSuccess = \case
LambdaInvokeSuccess {} -> Bool
True
LambdaInvokeError {} -> Bool
False
LambdaInvokeFailure {} -> Bool
False
data LambdaError = LambdaError
{ LambdaError -> Text
errorType :: Text
, LambdaError -> Text
errorMessage :: Text
, LambdaError -> [Text]
trace :: [Text]
}
deriving stock (Int -> LambdaError -> ShowS
[LambdaError] -> ShowS
LambdaError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LambdaError] -> ShowS
$cshowList :: [LambdaError] -> ShowS
show :: LambdaError -> String
$cshow :: LambdaError -> String
showsPrec :: Int -> LambdaError -> ShowS
$cshowsPrec :: Int -> LambdaError -> ShowS
Show, forall x. Rep LambdaError x -> LambdaError
forall x. LambdaError -> Rep LambdaError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LambdaError x -> LambdaError
$cfrom :: forall x. LambdaError -> Rep LambdaError x
Generic)
deriving anyclass (Value -> Parser [LambdaError]
Value -> Parser LambdaError
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [LambdaError]
$cparseJSONList :: Value -> Parser [LambdaError]
parseJSON :: Value -> Parser LambdaError
$cparseJSON :: Value -> Parser LambdaError
FromJSON, [LambdaError] -> Encoding
[LambdaError] -> Value
LambdaError -> Encoding
LambdaError -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [LambdaError] -> Encoding
$ctoEncodingList :: [LambdaError] -> Encoding
toJSONList :: [LambdaError] -> Value
$ctoJSONList :: [LambdaError] -> Value
toEncoding :: LambdaError -> Encoding
$ctoEncoding :: LambdaError -> Encoding
toJSON :: LambdaError -> Value
$ctoJSON :: LambdaError -> Value
ToJSON)
awsLambdaInvoke
:: ( MonadResource m
, MonadLogger m
, MonadReader env m
, HasAwsEnv env
, ToJSON a
)
=> Text
-> a
-> m LambdaInvokeResult
awsLambdaInvoke :: forall (m :: * -> *) env a.
(MonadResource m, MonadLogger m, MonadReader env m, HasAwsEnv env,
ToJSON a) =>
Text -> a -> m LambdaInvokeResult
awsLambdaInvoke Text
name a
payload = do
forall (m :: * -> *).
(HasCallStack, MonadLogger m) =>
Message -> m ()
logDebug forall a b. (a -> b) -> a -> b
$ Text
"Invoking function" Text -> [SeriesElem] -> Message
:# [Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
name]
InvokeResponse
resp <-
forall env (m :: * -> *) a.
(MonadReader env m, HasAwsEnv env) =>
Seconds -> m a -> m a
awsTimeout Seconds
905
forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) env a.
(MonadResource m, MonadReader env m, HasAwsEnv env, AWSRequest a,
Typeable a, Typeable (AWSResponse a)) =>
a -> m (AWSResponse a)
awsSend
forall a b. (a -> b) -> a -> b
$ Text -> ByteString -> Invoke
newInvoke Text
name
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BSL.toStrict
forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> ByteString
encode
a
payload
let
status :: Int
status = InvokeResponse
resp forall s a. s -> Getting a s a -> a
^. Lens' InvokeResponse Int
invokeResponse_statusCode
mError :: Maybe LambdaError
mError = forall a. FromJSON a => ByteString -> Maybe a
decode forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BSL.fromStrict forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< InvokeResponse
resp forall s a. s -> Getting a s a -> a
^. Lens' InvokeResponse (Maybe ByteString)
invokeResponse_payload
mFunctionError :: Maybe Text
mFunctionError = InvokeResponse
resp forall s a. s -> Getting a s a -> a
^. Lens' InvokeResponse (Maybe Text)
invokeResponse_functionError
response :: ByteString
response = forall a. a -> Maybe a -> a
fromMaybe ByteString
"" forall a b. (a -> b) -> a -> b
$ InvokeResponse
resp forall s a. s -> Getting a s a -> a
^. Lens' InvokeResponse (Maybe ByteString)
invokeResponse_payload
forall (m :: * -> *).
(HasCallStack, MonadLogger m) =>
Message -> m ()
logDebug
forall a b. (a -> b) -> a -> b
$ Text
"Function result"
Text -> [SeriesElem] -> Message
:# [ Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
name
, Key
"status" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
status
, Key
"error" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe LambdaError
mError
, Key
"functionError" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
mFunctionError
]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
forall a b. (a -> b) -> a -> b
$ if
| Int -> Bool
statusIsUnsuccessful Int
status -> Int -> Maybe Text -> LambdaInvokeResult
LambdaInvokeFailure Int
status Maybe Text
mFunctionError
| Just LambdaError
e <- Maybe LambdaError
mError -> LambdaError -> Maybe Text -> LambdaInvokeResult
LambdaInvokeError LambdaError
e Maybe Text
mFunctionError
| Bool
otherwise -> ByteString -> LambdaInvokeResult
LambdaInvokeSuccess ByteString
response
statusIsUnsuccessful :: Int -> Bool
statusIsUnsuccessful :: Int -> Bool
statusIsUnsuccessful Int
s = Int
s forall a. Ord a => a -> a -> Bool
< Int
200 Bool -> Bool -> Bool
|| Int
s forall a. Ord a => a -> a -> Bool
>= Int
300