infernal-0.2.0: The Infernal Machine - An AWS Lambda Custom Runtime for Haskell

Safe HaskellNone
LanguageHaskell2010

Infernal

Description

The Infernal Machine - An AWS Lambda Custom Runtime for Haskell

See runLambda or runSimpleLambda for entrypoints to build your Lambda function.

Synopsis

Documentation

type InitErrorCallback n = SomeException -> n LambdaError Source #

Error mapper for init errors. The result will be POSTed to the init error endpoint (docs). Exceptions of type LambdaError will not trigger this callback, and ExitCode will be rethrown after it executes.

type InvokeErrorCallback n = LambdaRequest -> SomeException -> n LambdaError Source #

Error mapper for invocation errors. The result will be POSTed to the invocation error endpoint (docs). Exceptions of type LambdaError will not trigger this callback, and ExitCode will be rethrown after it executes.

data LambdaError Source #

An error formatted to propagate to AWS (docs). Note that this is an Exception so you can throw it to short-circuit processing and report useful information. If you throw anything else a defaultLambdaError will be reported with no useful information.

Constructors

LambdaError 

Fields

Instances
Eq LambdaError Source # 
Instance details

Defined in Infernal

Show LambdaError Source # 
Instance details

Defined in Infernal

Generic LambdaError Source # 
Instance details

Defined in Infernal

Associated Types

type Rep LambdaError :: Type -> Type #

ToJSON LambdaError Source # 
Instance details

Defined in Infernal

Exception LambdaError Source # 
Instance details

Defined in Infernal

type Rep LambdaError Source # 
Instance details

Defined in Infernal

type Rep LambdaError = D1 (MetaData "LambdaError" "Infernal" "infernal-0.2.0-ArbNqjVbKhC64ON3Ujs82n" False) (C1 (MetaCons "LambdaError" PrefixI True) (S1 (MetaSel (Just "_lerrErrorType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_lerrErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data LambdaRequest Source #

The request parsed from the "next invocation" API (docs)

Constructors

LambdaRequest 

Fields

Instances
Eq LambdaRequest Source # 
Instance details

Defined in Infernal

Show LambdaRequest Source # 
Instance details

Defined in Infernal

data LambdaVars Source #

Environment variables set by AWS (docs). You may not need to read any of these, but the implementation needs the API endpoint var to handle requests.

Constructors

LambdaVars 

Fields

type RunCallback n = LambdaRequest -> n ByteString Source #

The "function" part of your Lambda: takes a request with a JSON-encoded body and returns a JSON-encoded response body. You can throw any Exception and the appropriate error callbacks will process it. Most importantly, LambdaError will propagate a formatted error to AWS, and ExitCode will halt the program. Except for ExitCode, throwing exceptions here will not terminate the main loop (see runLambda). Note that the AWS custom runtime loop implemented in this library is single-threaded (as required - we must finish an invocation before fetching the next) but you are free to spawn threads in your callback.

type UncaughtErrorCallback n = SomeException -> n () Source #

A handler for otherwise uncaught errors (like failures to fetch next invocation). These happen outside context in which we can report them to AWS, so there is no need to return a LambdaError. Exceptions of type ExitCode will be rethrown after this callback executes.

defaultLambdaError :: LambdaError Source #

A LambdaError that indicates a vague InternalError to AWS.

runLambda Source #

Arguments

:: (MonadCatch m, WithSimpleLog env m) 
=> UnliftIO n

Runs your monad n in IO (see MonadUnliftIO from unliftio-core)

-> InitErrorCallback n

Error mapper for the callback builder

-> (LambdaVars -> n (CallbackConfig n))

Callback builder. When possible, do init work here so the framework can propagate init errors to AWS.

-> m () 

The full-powered entrypoint underlying runSimpleLambda that allows you to use any UnliftIO-capable monad for your callbacks. This runs the main loop of our AWS Lambda Custom Runtime to fetch invocations, process them, and report errors or results. Control will not return from this function, and AWS Lambda will terminate the process at its will.

runSimpleLambda :: RunCallback (RIO App) -> IO () Source #

A simple entrypoint that delegates to runLambda. Use this as the body of your main function if you want to get a Lambda function up and running quickly. All you need to do is provide a RunCallback that handles JSON-encoded requests and returns JSON-encoded responses (or throws LambdaError exceptions). Your callback has access to a simple logger (try logDebug, for example) whose output will be collected by Lambda and published to CloudWatch.