| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
AWSLambda.Events.APIGateway
Description
Based on https://github.com/aws/aws-lambda-dotnet/tree/master/Libraries/src/Amazon.Lambda.APIGatewayEvents
To enable processing of API Gateway events, use the events key in
serverless.yml as usual:
functions:
myapifunc:
handler: mypackage.mypackage-exe
events:
- http:
path: hello/{name}
method: getThen use apiGatewayMain in the handler to process the requests.
Synopsis
- type Method = Text
- type HeaderName = Text
- type HeaderValue = Text
- type QueryParamName = Text
- type QueryParamValue = Text
- type PathParamName = Text
- type PathParamValue = Text
- type StageVarName = Text
- type StageVarValue = Text
- data RequestIdentity = RequestIdentity {
- _riCognitoIdentityPoolId :: !(Maybe Text)
- _riAccountId :: !(Maybe Text)
- _riCognitoIdentityId :: !(Maybe Text)
- _riCaller :: !(Maybe Text)
- _riApiKey :: !(Maybe Text)
- _riSourceIp :: !(Maybe IP)
- _riCognitoAuthenticationType :: !(Maybe Text)
- _riCognitoAuthenticationProvider :: !(Maybe Text)
- _riUserArn :: !(Maybe Text)
- _riUserAgent :: !(Maybe Text)
- _riUser :: !(Maybe Text)
- readParse :: Read a => String -> Text -> Parser a
- riUserArn :: Lens' RequestIdentity (Maybe Text)
- riUserAgent :: Lens' RequestIdentity (Maybe Text)
- riUser :: Lens' RequestIdentity (Maybe Text)
- riSourceIp :: Lens' RequestIdentity (Maybe IP)
- riCognitoIdentityPoolId :: Lens' RequestIdentity (Maybe Text)
- riCognitoIdentityId :: Lens' RequestIdentity (Maybe Text)
- riCognitoAuthenticationType :: Lens' RequestIdentity (Maybe Text)
- riCognitoAuthenticationProvider :: Lens' RequestIdentity (Maybe Text)
- riCaller :: Lens' RequestIdentity (Maybe Text)
- riApiKey :: Lens' RequestIdentity (Maybe Text)
- riAccountId :: Lens' RequestIdentity (Maybe Text)
- data Authorizer = Authorizer {}
- aPrincipalId :: Lens' Authorizer (Maybe Text)
- aContext :: Lens' Authorizer Object
- aClaims :: Lens' Authorizer Object
- data ProxyRequestContext = ProxyRequestContext {
- _prcPath :: !(Maybe Text)
- _prcAccountId :: !Text
- _prcResourceId :: !Text
- _prcStage :: !Text
- _prcRequestId :: !Text
- _prcIdentity :: !RequestIdentity
- _prcResourcePath :: !Text
- _prcHttpMethod :: !Text
- _prcApiId :: !Text
- _prcProtocol :: !Text
- _prcAuthorizer :: !(Maybe Authorizer)
- prcStage :: Lens' ProxyRequestContext Text
- prcResourcePath :: Lens' ProxyRequestContext Text
- prcResourceId :: Lens' ProxyRequestContext Text
- prcRequestId :: Lens' ProxyRequestContext Text
- prcProtocol :: Lens' ProxyRequestContext Text
- prcPath :: Lens' ProxyRequestContext (Maybe Text)
- prcIdentity :: Lens' ProxyRequestContext RequestIdentity
- prcHttpMethod :: Lens' ProxyRequestContext Text
- prcAuthorizer :: Lens' ProxyRequestContext (Maybe Authorizer)
- prcApiId :: Lens' ProxyRequestContext Text
- prcAccountId :: Lens' ProxyRequestContext Text
- data APIGatewayProxyRequest body = APIGatewayProxyRequest {
- _agprqResource :: !Text
- _agprqPath :: !ByteString
- _agprqHttpMethod :: !Method
- _agprqHeaders :: !RequestHeaders
- _agprqQueryStringParameters :: !Query
- _agprqPathParameters :: !(HashMap PathParamName PathParamValue)
- _agprqStageVariables :: !(HashMap StageVarName StageVarValue)
- _agprqRequestContext :: !ProxyRequestContext
- _agprqBody :: !(Maybe (TextValue body))
- agprqStageVariables :: forall body. Lens' (APIGatewayProxyRequest body) (HashMap StageVarName StageVarValue)
- agprqResource :: forall body. Lens' (APIGatewayProxyRequest body) Text
- agprqRequestContext :: forall body. Lens' (APIGatewayProxyRequest body) ProxyRequestContext
- agprqQueryStringParameters :: forall body. Lens' (APIGatewayProxyRequest body) Query
- agprqPathParameters :: forall body. Lens' (APIGatewayProxyRequest body) (HashMap PathParamName PathParamValue)
- agprqPath :: forall body. Lens' (APIGatewayProxyRequest body) ByteString
- agprqHttpMethod :: forall body. Lens' (APIGatewayProxyRequest body) Method
- agprqHeaders :: forall body. Lens' (APIGatewayProxyRequest body) RequestHeaders
- agprqBody :: forall body body. Lens (APIGatewayProxyRequest body) (APIGatewayProxyRequest body) (Maybe (TextValue body)) (Maybe (TextValue body))
- requestBody :: Getter (APIGatewayProxyRequest body) (Maybe body)
- requestBodyEmbedded :: Getter (APIGatewayProxyRequest (Embedded v)) (Maybe v)
- requestBodyBinary :: Getter (APIGatewayProxyRequest Base64) (Maybe ByteString)
- data APIGatewayProxyResponse body = APIGatewayProxyResponse {
- _agprsStatusCode :: !Int
- _agprsHeaders :: !ResponseHeaders
- _agprsBody :: !(Maybe (TextValue body))
- agprsStatusCode :: forall body. Lens' (APIGatewayProxyResponse body) Int
- agprsHeaders :: forall body. Lens' (APIGatewayProxyResponse body) ResponseHeaders
- agprsBody :: forall body body. Lens (APIGatewayProxyResponse body) (APIGatewayProxyResponse body) (Maybe (TextValue body)) (Maybe (TextValue body))
- response :: Int -> APIGatewayProxyResponse body
- responseOK :: APIGatewayProxyResponse body
- responseNotFound :: APIGatewayProxyResponse body
- responseBadRequest :: APIGatewayProxyResponse body
- responseBody :: Setter' (APIGatewayProxyResponse body) (Maybe body)
- responseBodyEmbedded :: Setter' (APIGatewayProxyResponse (Embedded body)) (Maybe body)
- responseBodyBinary :: Setter' (APIGatewayProxyResponse Base64) (Maybe ByteString)
- apiGatewayMain :: (FromText reqBody, ToText resBody) => (APIGatewayProxyRequest reqBody -> IO (APIGatewayProxyResponse resBody)) -> IO ()
Documentation
type HeaderName = Text Source #
type HeaderValue = Text Source #
type QueryParamName = Text Source #
type QueryParamValue = Text Source #
type PathParamName = Text Source #
type PathParamValue = Text Source #
type StageVarName = Text Source #
type StageVarValue = Text Source #
data RequestIdentity Source #
Constructors
| RequestIdentity | |
Fields
| |
Instances
| Eq RequestIdentity Source # | |
Defined in AWSLambda.Events.APIGateway Methods (==) :: RequestIdentity -> RequestIdentity -> Bool # (/=) :: RequestIdentity -> RequestIdentity -> Bool # | |
| Show RequestIdentity Source # | |
Defined in AWSLambda.Events.APIGateway Methods showsPrec :: Int -> RequestIdentity -> ShowS # show :: RequestIdentity -> String # showList :: [RequestIdentity] -> ShowS # | |
| FromJSON RequestIdentity Source # | |
Defined in AWSLambda.Events.APIGateway Methods parseJSON :: Value -> Parser RequestIdentity # parseJSONList :: Value -> Parser [RequestIdentity] # | |
riSourceIp :: Lens' RequestIdentity (Maybe IP) Source #
data Authorizer Source #
Constructors
| Authorizer | |
Instances
| Eq Authorizer Source # | |
Defined in AWSLambda.Events.APIGateway | |
| Show Authorizer Source # | |
Defined in AWSLambda.Events.APIGateway Methods showsPrec :: Int -> Authorizer -> ShowS # show :: Authorizer -> String # showList :: [Authorizer] -> ShowS # | |
| FromJSON Authorizer Source # | |
Defined in AWSLambda.Events.APIGateway | |
aPrincipalId :: Lens' Authorizer (Maybe Text) Source #
data ProxyRequestContext Source #
Constructors
| ProxyRequestContext | |
Fields
| |
Instances
| Eq ProxyRequestContext Source # | |
Defined in AWSLambda.Events.APIGateway Methods (==) :: ProxyRequestContext -> ProxyRequestContext -> Bool # (/=) :: ProxyRequestContext -> ProxyRequestContext -> Bool # | |
| Show ProxyRequestContext Source # | |
Defined in AWSLambda.Events.APIGateway Methods showsPrec :: Int -> ProxyRequestContext -> ShowS # show :: ProxyRequestContext -> String # showList :: [ProxyRequestContext] -> ShowS # | |
| FromJSON ProxyRequestContext Source # | |
Defined in AWSLambda.Events.APIGateway Methods parseJSON :: Value -> Parser ProxyRequestContext # parseJSONList :: Value -> Parser [ProxyRequestContext] # | |
data APIGatewayProxyRequest body Source #
Constructors
| APIGatewayProxyRequest | |
Fields
| |
Instances
agprqStageVariables :: forall body. Lens' (APIGatewayProxyRequest body) (HashMap StageVarName StageVarValue) Source #
agprqResource :: forall body. Lens' (APIGatewayProxyRequest body) Text Source #
agprqRequestContext :: forall body. Lens' (APIGatewayProxyRequest body) ProxyRequestContext Source #
agprqQueryStringParameters :: forall body. Lens' (APIGatewayProxyRequest body) Query Source #
agprqPathParameters :: forall body. Lens' (APIGatewayProxyRequest body) (HashMap PathParamName PathParamValue) Source #
agprqPath :: forall body. Lens' (APIGatewayProxyRequest body) ByteString Source #
agprqHttpMethod :: forall body. Lens' (APIGatewayProxyRequest body) Method Source #
agprqHeaders :: forall body. Lens' (APIGatewayProxyRequest body) RequestHeaders 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 #
Constructors
| APIGatewayProxyResponse | |
Fields
| |
Instances
agprsStatusCode :: forall body. Lens' (APIGatewayProxyResponse body) Int Source #
agprsHeaders :: forall body. Lens' (APIGatewayProxyResponse body) ResponseHeaders Source #
agprsBody :: forall body body. Lens (APIGatewayProxyResponse body) (APIGatewayProxyResponse body) (Maybe (TextValue body)) (Maybe (TextValue body)) Source #
response :: Int -> APIGatewayProxyResponse body Source #
responseOK :: APIGatewayProxyResponse body Source #
responseBody :: Setter' (APIGatewayProxyResponse body) (Maybe body) Source #
responseBodyEmbedded :: Setter' (APIGatewayProxyResponse (Embedded body)) (Maybe body) 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.