distributed-fork-aws-lambda-0.0.2.0: AWS Lambda backend for distributed-fork.

Safe HaskellNone
LanguageHaskell2010

Control.Distributed.Fork.Lambda

Contents

Description

Provides a Backend using AWS Lambda functions.

In order to do that, roughly:

  • It creates a deployment archive containing the program binary and a tiny wrapper written in Python and uploads it to the given S3 bucket.
  • Creates a CloudFormation stack containing the Lambda function and an SQS queue to gather the answers.
  • It starts polling the SQS queue for any answers.
  • When executing, it invokes the Lambda function using asynchronous invocation mode and blocks until a message appears in the queue.
  • On exit, it deletes the CloudFormation stack.

Some warts:

  • The same binary should run on AWS Lambda. In practice, this means:

    • You have to build and use this library on a Linux machine.
    • You have to statically link everything. You can use GHC's '-static -optl-static -optl-pthread -fPIC' parameters for that. See examples/examples.cabal#L16 for an example.
  • On AWS Lambda, more memory you assign to a function, more CPU you get. So it might make your function run faster if you overallocate memory.
  • When invoked asynchronously, AWS Lambda retries the invocation 2 more times waiting a minute between every retry. This means when something fails, it will take at least a few minutes to until you get an exception.

Synopsis

Usage

withLambdaBackend :: LambdaBackendOptions -> (Backend -> IO a) -> IO a Source #

Provides a Backend using AWS Lambda functions.

Created AWS resources except the uploaded deployment package will be cleaned up when exiting.

Example usage:

{-# LANGUAGE StaticPointers #-}

import Control.Lens
import Control.Distributed.Fork
import Control.Distributed.Fork.Lambda

opts :: LambdaBackendOptions
opts = lambdaBackendOptions "my-s3-bucket"
         & lboMemory .~ 1024

main :: IO ()
main = do
  initDistributedFork
  withLambdaBackend opts $ \backend -> do
    handle <- fork backend (static Dict) (static (return "Hello from Lambda!"))
    await handle >>= putStrLn

Options

data LambdaBackendOptions Source #

Options required for creating a Lambda backend.

Use lambdaBackendOptions smart constructor to create and lenses below for setting optional fields.

lambdaBackendOptions Source #

Arguments

:: Text

Name of the S3 bucket to store the deployment archive in.

-> LambdaBackendOptions 

lboPrefix :: Lens' LambdaBackendOptions Text Source #

Prefix to the deployment archive and the CloudFormation stack.

Default: "distributed-fork"

lboMemory :: Lens' LambdaBackendOptions Int Source #

Desired memory for the Lambda functions.

See CloudFormation's AWS::Lambda::Function::MemorySize page for allowed values.

Default: 128