serverless-haskell-0.4.2: Deploying Haskell code onto AWS Lambda using Serverless

Safe HaskellNone
LanguageHaskell2010

AWSLambda.Events.APIGateway

Description

Synopsis

Documentation

data APIGatewayProxyRequest body Source #

Instances

Eq body => Eq (APIGatewayProxyRequest body) Source # 
Show body => Show (APIGatewayProxyRequest body) Source # 
Generic (APIGatewayProxyRequest body) Source # 

Associated Types

type Rep (APIGatewayProxyRequest body) :: * -> * #

FromText body => FromJSON (APIGatewayProxyRequest body) Source # 
type Rep (APIGatewayProxyRequest body) Source # 

agprqBody :: forall body body. Lens (APIGatewayProxyRequest body) (APIGatewayProxyRequest body) (Maybe (TextValue body)) (Maybe (TextValue body)) Source #

requestBody :: Getter (APIGatewayProxyRequest body) (Maybe body) Source #

Get the request body, if there is one

requestBodyEmbedded :: Getter (APIGatewayProxyRequest (Embedded v)) (Maybe v) Source #

Get the embedded request body, if there is one

requestBodyBinary :: Getter (APIGatewayProxyRequest Base64) (Maybe ByteString) Source #

Get the binary (decoded Base64) request body, if there is one

data APIGatewayProxyResponse body Source #

Instances

Eq body => Eq (APIGatewayProxyResponse body) Source # 
Show body => Show (APIGatewayProxyResponse body) Source # 
Generic (APIGatewayProxyResponse body) Source # 

Associated Types

type Rep (APIGatewayProxyResponse body) :: * -> * #

ToText body => ToJSON (APIGatewayProxyResponse body) Source # 
FromText body => FromJSON (APIGatewayProxyResponse body) Source # 
type Rep (APIGatewayProxyResponse body) Source # 
type Rep (APIGatewayProxyResponse body) = D1 * (MetaData "APIGatewayProxyResponse" "AWSLambda.Events.APIGateway" "serverless-haskell-0.4.2-9tK1nYD52iX70aHhOdwebv" False) (C1 * (MetaCons "APIGatewayProxyResponse" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_agprsStatusCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "_agprsHeaders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (HashMap HeaderName HeaderValue))) (S1 * (MetaSel (Just Symbol "_agprsBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (TextValue body)))))))

apiGatewayMain Source #

Arguments

:: (FromText reqBody, ToText resBody) 
=> (APIGatewayProxyRequest reqBody -> IO (APIGatewayProxyResponse resBody))

Function to process the event

-> IO () 

Process incoming events from serverless-haskell using a provided function.

This is a specialisation of lambdaMain for API Gateway.

The handler receives the input event given to the AWS Lambda function, and its return value is returned from the function.

This is intended to be used as main, for example:

import AWSLambda.Events.APIGateway
import Control.Lens
import Data.Aeson
import Data.Aeson.Embedded

main = apiGatewayMain handler

handler :: APIGatewayProxyRequest (Embedded Value) -> IO (APIGatewayProxyResponse (Embedded [Int]))
handler request = do
  putStrLn "This should go to logs"
  print $ request ^. requestBody
  pure $ responseOK & responseBodyEmbedded ?~ [1, 2, 3]

The type parameters reqBody and resBody represent the types of request and response body, respectively. The FromText and ToText contraints are required because these values come from string fields in the request and response JSON objects. To get direct access to the body string, use Text as the parameter type. To treat the body as a stringified embedded JSON value, use Embedded a, where a has the appropriate FromJSON or ToJSON instances. To treat the body as base 64 encoded binary use Base64.