hal-0.1.0: Please see the README.md file for this project.

Copyright(c) Nike Inc. 2018
LicenseBSD3
Maintainernathan.fairhurst@nike.com, fernando.freire@nike.com
Stabilitystable
Safe HaskellNone
LanguageHaskell2010

AWS.Lambda.Runtime

Description

 
Synopsis

Documentation

pureRuntime :: (FromJSON event, ToJSON result) => (event -> 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 (FromJSON)

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

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

    main :: IO ()
    main = pureRuntime myHandler

pureRuntimeWithContext :: (FromJSON event, ToJSON result) => (LambdaContext -> event -> 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 (FromJSON)
    import Data.Text (unpack)

    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 = pureRuntimeWithContext myHandler

fallibleRuntime :: (FromJSON event, ToJSON result) => (event -> 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 (FromJSON)

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

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

    main :: IO ()
    main = fallibleRuntime myHandler

fallibleRuntimeWithContext :: (FromJSON event, ToJSON result) => (LambdaContext -> event -> 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 (FromJSON)
    import Data.Text (unpack)

    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 = fallibleRuntimeWithContext myHandler

ioRuntime :: (FromJSON event, ToJSON result) => (event -> 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 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 = ioRuntime myHandler

ioRuntimeWithContext :: (FromJSON event, ToJSON result) => (LambdaContext -> event -> 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 Data.Aeson (FromJSON)
    import Data.Text (unpack)
    import System.Environment (getEnv)

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

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

    main :: IO ()
    main = ioRuntimeWithContext myHandler

readerTRuntime :: (FromJSON event, ToJSON result) => (event -> 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 Data.Aeson (FromJSON)
    import Data.Text (unpack)
    import System.Environment (getEnv)

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

    myHandler :: Named -> ReaderT LambdaContext IO String
    myHandler Named { name } = do
      LambdaContext { functionName } <- ask
      greeting <- getEnv "GREETING"
      return $ greeting ++ name ++ " from " ++ unpack functionName ++ "!"

    main :: IO ()
    main = readerTRuntime myHandler

mRuntimeWithContext :: (HasLambdaContext r, MonadCatch m, MonadReader r m, MonadIO m, FromJSON event, ToJSON result) => (event -> m result) -> m () Source #

For any monad that supports IOcatchReader LambdaContext.

Use this if you need caching behavours or are comfortable manipulating monad transformers and want full control over your monadic interface.

    {-# LANGUAGE NamedFieldPuns, DeriveGeneric #-}

    module Main where

    import AWS.Lambda.Context (LambdaContext(..))
    import AWS.Lambda.Runtime (mRuntimeWithContext)
    import Control.Monad.Reader (ReaderT, ask)
    import Control.Monad.State.Lazy (StateT, runStateT, get, put)
    import Data.Aeson (FromJSON)
    import Data.Text (unpack)
    import System.Environment (getEnv)

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

    myHandler :: Named -> StateT Int (ReaderT LambdaContext IO String)
    myHandler Named { name } = do
      LambdaContext { functionName } <- ask
      greeting <- getEnv "GREETING"

      greetingCount <- get
      put $ greetingCount + 1

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

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