hal-0.3.0: 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 HaskellNone
LanguageHaskell2010

AWS.Lambda.Combinators

Description

These combinators are for those who need to peek below the abstraction of the basic runtimes, for whatever reason.

They map functions (instead of values) to turn basic handlers into handlers compatible with the base runtime. These combinators allow us to expose functionality across many dimensions in an abstract way. It also allows simple building blocks for those who need to "get in the middle" or adapt the basic runtimes in new ways without rebuilding everything from the ground up.

Synopsis

Documentation

withIOInterface :: (MonadReader c m, MonadIO m) => (c -> b -> IO (Either String a)) -> b -> m a Source #

Upgrades a handler that uses the IO monad with an Either inside into a base runtime handler.

In the example below, we reconstruct ioRuntimeWithContext without actually using it. The readerTRuntime expects a handler in the form of event -> ReaderT LambdaContext IO result (ignoring constraints). By composing it with withIOInterface we get a new runtime which expects a function in the form of LambdaContext -> event -> IO result which matches that of myHandler.

    {-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

    module Main where

    import AWS.Lambda.Runtime (readerTRuntime)
    import AWS.Lambda.Combinators (withIOInterface)
    import Data.Aeson (FromJSON)
    import System.Environment (getEnv)

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

    myHandler :: Named -> IO String
    myHandler (Named { name }) = do
      greeting <- getEnv "GREETING"
      return $ greeting ++ name

    main :: IO ()
    main = (readerTRuntime . withIOInterface) myHandler

withFallibleInterface :: MonadReader c m => (c -> b -> Either String a) -> b -> m a Source #

Upgrades a handler that accepts LambdaContext and an event to return a value inside an Either inside into a base runtime handler.

In the example below, we reconstruct fallibleRuntimeWithContext without actually using it. The readerTRuntime expects a handler in the form of event -> ReaderT LambdaContext IO result (ignoring constraints). By composing it with withFallibleInterface we get a new runtime which expects a function in the form of LambdaContext -> event -> Either String result which matches that of myHandler.

    {-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

    module Main where

    import AWS.Lambda.Runtime (readerTRuntime)
    import AWS.Lambda.Combinators (withFallibleInterface)
    import Data.Aeson (FromJSON)
    import System.Environment (getEnv)

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

    myHandler :: LambdaContext -> Named -> Either String String
    myHandler (LambdaContext { functionName }) (Named { name }) =
      if name == "World" then
        Right "Hello, World from " ++ unpack functionName ++ "!"
      else
        Left "Can only greet the world."

    main :: IO ()
    main = (readerTRuntime . withFallibleInterface) myHandler

withPureInterface :: MonadReader c m => (c -> b -> a) -> b -> m a Source #

This combinator takes a handler that accepts both an event and LambdaContext and converts it into a handler that is compatible with the base monadic runtime.

In the example below, we reconstruct pureRuntimeWithContext without actually using it. The readerTRuntime expects a handler in the form of event -> ReaderT LambdaContext IO result (ignoring constraints). By composing it with withPureInterface we get a new runtime which expects a function in the form of LambdaContext -> event -> result which matches that of myHandler.

    {-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

    module Main where

    import AWS.Lambda.Runtime (readerTRuntime)
    import AWS.Lambda.Combinators (withPureInterface)
    import Data.Aeson (FromJSON)

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

    myHandler :: LambdaContext -> Named -> String
    myHandler (LambdaContext { functionName }) (Named { name }) =
      "Hello, " ++ name ++ " from " ++ unpack functionName ++ "!"

    main :: IO ()
    main = (readerTRuntime . withPureInterface) myHandler

withoutContext :: a -> b -> a Source #

An alias of const, this upgrades a handler that does not accept LambdaContext as its first curried argument to one that does.

This allows us to use other combinators to construct a lambda runtime that accepts a handler that ignores LambdaContext.

In the example below, we reconstruct pureRuntime without actually using it. The readerTRuntime expects a handler in the form of event -> ReaderT LambdaContext IO result (ignoring constraints). By composing it with withPureInterface we get a new runtime which expects a function in the form of LambdaContext -> event -> result, And then finally we also compose withoutContext so it accepts the signature event -> result which matches that of myHandler.

    {-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

    module Main where

    import AWS.Lambda.Runtime (readerTRuntime)
    import AWS.Lambda.Combinators (withPureInterface, withoutContext)
    import Data.Aeson (FromJSON)

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

    myHandler :: Named -> String
    myHandler (Named { name }) =
      "Hello, " ++ name

    main :: IO ()
    main = (readerTRuntime . withPureInterface . withoutContext) myHandler