hal-1.0.0.1: A runtime environment for Haskell applications running on AWS Lambda.
Copyright(c) Nike Inc. 2018
LicenseBSD3
Maintainernathan.fairhurst@nike.com, fernando.freire@nike.com
Stabilitystable
Safe HaskellSafe-Inferred
LanguageHaskell2010

AWS.Lambda.Runtime.Value

Description

These are runtimes designed for AWS Lambda, which accept a handler and return an application that will retreive and execute events as long as a container continues to exist.

These runtimes expect handlers that accept a parsed JSON AST (Value) as the input, instead some particular type with a FromJSON instance. Handlers using these runtimes must take care of the conversion and handle errors explicitly. Handlers that should throw an exception or never expect to be invoked with an invalid payload, should simply use the runtimes in the AWS.Lambda.Runtime module.

Each example shows the conversion from the Value type to the target FromJSON type.

Many of these runtimes use AWS.Lambda.Combinators under the hood. For those interested in peeking below the abstractions provided here, please refer to that module.

Synopsis

Documentation

pureRuntime :: ToJSON result => (Value -> result) -> IO () Source #

For pure functions that can never fail.

Use this for simple handlers that just translate input to output without side-effects.

{-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

module Main where

import AWS.Lambda.Runtime (pureRuntime)
import Data.Aeson (Value, FromJSON, parseJSON)
import Data.Aeson.Types (parseMaybe)
import GHC.Generics (Generic)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: Value -> String
myHandler jsonAst =
  case parseMaybe parseJSON jsonAst of
    Nothing -> "My name is HAL, what's yours?"
    Just Named { name } ->
      "Hello, " ++ name ++ "!"

main :: IO ()
main = pureRuntime myHandler

pureRuntimeWithContext :: ToJSON result => (LambdaContext -> Value -> result) -> IO () Source #

For pure functions that can never fail that also need access to the context.

Use this for simple handlers that just translate input to output without side-effects, but that need the AWS Lambda Context as input.

{-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

module Main where

import AWS.Lambda.Context (LambdaContext(..))
import AWS.Lambda.Runtime (pureRuntimeWithContext)
import Data.Aeson (Value, FromJSON, parseJSON)
import Data.Aeson.Types (parseMaybe)
import Data.Text (unpack)
import GHC.Generics (Generic)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: LambdaContext -> Value -> Either String String
myHandler (LambdaContext { functionName }) jsonAst =
  case parseMaybe parseJSON jsonAst of
    Nothing -> Right "My name is HAL, what's yours?"
    Just Named { name } ->
      Right $ "Hello, " ++ name ++ " from " ++ unpack functionName ++ "!"

main :: IO ()
main = pureRuntimeWithContext myHandler

fallibleRuntime :: ToJSON result => (Value -> Either String result) -> IO () Source #

For pure functions that can still fail.

Use this for simple handlers that just translate input to output without side-effects, but can fail.

{-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

module Main where

import AWS.Lambda.Runtime (fallibleRuntime)
import Data.Aeson (Value, FromJSON, parseJSON)
import Data.Aeson.Types (parseMaybe)
import GHC.Generics (Generic)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: Value -> Either String String
myHandler jsonAst =
  case parseMaybe parseJSON jsonAst of
    Nothing -> Right "My name is HAL, what's yours?"
    Just Named { name } ->
      if name == "World" then
        Right "Hello, World!"
      else
        Left "Can only greet the world."

main :: IO ()
main = fallibleRuntime myHandler

fallibleRuntimeWithContext :: ToJSON result => (LambdaContext -> Value -> Either String result) -> IO () Source #

For pure functions that can still fail.

Use this for simple handlers that just translate input to output without side-effects, but can fail and need the AWS Lambda Context as input.

{-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

module Main where

import AWS.Lambda.Context (LambdaContext(..))
import AWS.Lambda.Runtime (fallibleRuntimeWithContext)
import Data.Aeson (Value, FromJSON, parseJSON)
import Data.Aeson.Types (parseMaybe)
import Data.Text (unpack)
import GHC.Generics (Generic)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: LambdaContext -> Value -> Either String String
myHandler (LambdaContext { functionName }) jsonAst =
  case parseMaybe parseJSON jsonAst of
    Nothing -> Right "My name is HAL, what's yours?"
    Just Named { name } ->
      if name == "World" then
        Right $ "Hello, World from " ++ unpack functionName ++ "!"
      else
        Left "Can only greet the world."

main :: IO ()
main = fallibleRuntimeWithContext myHandler

ioRuntime :: ToJSON result => (Value -> IO (Either String result)) -> IO () Source #

For functions with IO that can fail in a pure way (or via throw).

Use this for handlers that need any form of side-effect such as reading environment variables or making network requests. However, do not use this runtime if you need stateful (caching) behaviors.

{-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

module Main where

import AWS.Lambda.Runtime (ioRuntime)
import Control.Monad.Trans (liftIO)
import Data.Aeson (Value, FromJSON, parseJSON)
import Data.Aeson.Types (parseMaybe)
import System.Environment (getEnv)
import GHC.Generics (Generic)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: Value -> IO (Either String String)
myHandler jsonAst =
  case parseMaybe parseJSON jsonAst of
    Nothing -> return $ pure "My name is HAL, what's yours?"
    Just Named { name } -> do
      greeting <- liftIO $ getEnv "GREETING"
      return $ pure $ greeting ++ name

main :: IO ()
main = ioRuntime myHandler

ioRuntimeWithContext :: ToJSON result => (LambdaContext -> Value -> IO (Either String result)) -> IO () Source #

For functions with IO that can fail in a pure way (or via throw).

Use this for handlers that need any form of side-effect such as reading environment variables or making network requests, and also need the AWS Lambda Context as input. However, do not use this runtime if you need stateful (caching) behaviors.

{-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

module Main where

import AWS.Lambda.Context (LambdaContext(..))
import AWS.Lambda.Runtime (ioRuntimeWithContext)
import Control.Monad.Trans (liftIO)
import Data.Aeson (Value, FromJSON, parseJSON)
import Data.Aeson.Types (parseMaybe)
import Data.Text (unpack)
import System.Environment (getEnv)
import GHC.Generics (Generic)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: LambdaContext -> Value -> IO (Either String String)
myHandler (LambdaContext { functionName }) jsonAst =
  case parseMaybe parseJSON jsonAst of
    Nothing -> return $ pure "My name is HAL, what's yours?"
    Just Named { name } -> do
      greeting <- liftIO $ getEnv "GREETING"
      return $ pure $ greeting ++ name ++ " from " ++ unpack functionName ++ "!"

main :: IO ()
main = ioRuntimeWithContext myHandler

readerTRuntime :: ToJSON result => (Value -> ReaderT LambdaContext IO result) -> IO () Source #

For functions that can read the lambda context and use IO within the same monad.

Use this for handlers that need any form of side-effect such as reading environment variables or making network requests, and prefer to access the AWS Lambda Context in the same monad. However, do not use this runtime if you need stateful (caching) behaviors.

{-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

module Main where

import AWS.Lambda.Context (LambdaContext(..))
import AWS.Lambda.Runtime (readerTRuntime)
import Control.Monad.Reader (ReaderT, ask)
import Control.Monad.Trans (liftIO)
import Data.Aeson (Value, FromJSON, parseJSON)
import Data.Aeson.Types (parseMaybe)
import Data.Text (unpack)
import System.Environment (getEnv)
import GHC.Generics (Generic)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: Value -> ReaderT LambdaContext IO String
myHandler jsonAst =
  case parseMaybe parseJSON jsonAst of
    Nothing -> return $ "My name is HAL, what's yours?"
    Just Named { name } -> do
      LambdaContext { functionName } <- ask
      greeting <- liftIO $ getEnv "GREETING"
      return $ greeting ++ name ++ " from " ++ unpack functionName ++ "!"

main :: IO ()
main = readerTRuntime myHandler

mRuntime :: (MonadCatch m, MonadIO m, ToJSON result) => (Value -> m result) -> m () Source #

For any monad that supports IO and catch. Useful if you need caching behaviours or are comfortable manipulating monad transformers, want full control over your monadic interface, but don't need to inspect the LambdaContext.

A contrived example, that parses the Value argument directly instead of using the higher-level features in AWS.Lambda.Runtime.Value:

{-# LANGUAGE DeriveAnyClass, DeriveGeneric, NamedFieldPuns #-}

module Main where

import AWS.Lambda.Runtime (mRuntime)
import Control.Monad.Catch (Exception, throwM)
import Control.Monad.State.Lazy (StateT, evalStateT, get, put)
import Control.Monad.Trans (liftIO)
import Data.Aeson (FromJSON, Result(..), Value, fromJSON)
import System.Environment (getEnv)
import GHC.Generics (Generic)

data AesonParseException = AesonParseException String
  deriving (Show, Exception)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler ::  Value -> StateT Int IO String
myHandler value = do
  greeting <- liftIO $ getEnv "GREETING"
  Named { name } <- case fromJSON value of
    Error err -> throwM $ AesonParseException err
    Success named -> pure named
  greetingCount <- get
  put $ greetingCount + 1

  return $ greeting ++ name ++ " (" ++ show greetingCount ++ ")!"

main :: IO ()
main = evalStateT (mRuntime myHandler) 0

mRuntimeWithContext :: (MonadCatch m, MonadIO m, ToJSON result) => (LambdaContext -> Value -> m result) -> m () Source #

For any monad that supports IO and catch. Useful if you need caching behaviours or are comfortable manipulating monad transformers, and want full control over your monadic interface.

A contrived example, that parses the Value argument directly instead of using the higher-level features in AWS.Lambda.Runtime.Value:

{-# LANGUAGE DeriveAnyClass, DeriveGeneric, NamedFieldPuns #-}

module Main where

import AWS.Lambda.Context (LambdaContext(..))
import AWS.Lambda.Runtime (mRuntimeWithContext)
import Control.Monad.Catch (Exception, throwM)
import Control.Monad.State.Lazy (StateT, evalStateT, get, put)
import Control.Monad.Trans (liftIO)
import Data.Aeson (FromJSON, Result(..), Value, fromJSON)
import Data.Text (unpack)
import System.Environment (getEnv)
import GHC.Generics (Generic)

data AesonParseException = AesonParseException String
  deriving (Show, Exception)

data Named = Named {
  name :: String
} deriving Generic
instance FromJSON Named

myHandler :: LambdaContext -> Value -> StateT Int IO String
myHandler LambdaContext { functionName } value = do
  greeting <- liftIO $ getEnv "GREETING"
  Named { name } <- case fromJSON value of
    Error err -> throwM $ AesonParseException err
    Success named -> pure named
  greetingCount <- get
  put $ greetingCount + 1

  return $ greeting ++ name ++ " (" ++ show greetingCount ++ ") from " ++ unpack functionName ++ "!"

main :: IO ()
main = evalStateT (mRuntimeWithContext myHandler) 0