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

AWS.Lambda.Events.ApiGateway.ProxyResponse

Description

This module enable exposes the required types for responding to API Gateway Proxy Events. Responses must return a status, body, and optionaly headers. Multiple smart contructors and helpers are provided to help encapsulated details like header case-insensitivity, multiple header copies, correct base64 encoding, and default content type.

Synopsis

Documentation

data ProxyResponse Source #

A response returned to an API Gateway when using the HTTP Lambda Proxy integration. ContentType will be set based on the ProxyBody (recommended) if a value is not present in the headers field.

This type can be constructed explicity or via the smart constructor response. Headers can then be added incrementally with addHeader or setHeader. The smart constructor pattern is recommended because it avoids some of the awkwardness of dealing with the multiValueHeaders field's type.

{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import AWS.Lambda.Runtime (pureRuntime)
import AWS.Lambda.Events.ApiGateway.ProxyRequest (ProxyRequest(..), NoAuthorizer)
import AWS.Lambda.Events.ApiGateway.ProxyResponse (ProxyResponse(..), textPlain, forbidden403, ok200, response)

myHandler :: ProxyRequest NoAuthorizer -> ProxyResponse
myHandler ProxyRequest { httpMethod = "GET", path = "/say_hello" } =
    -- Smart Constructor and added header (recommended)
    addHeader "My-Custom-Header" Value $
      response ok200 $ textPlain "Hello"
myHandler _ =
    -- Explicit Construction (not recommended)
    ProxyResponse
    {   status = forbidden403
    ,   body = textPlain "Forbidden"
    ,   multiValueHeaders =
          fromList [(mk "My-Custom-Header", ["Other Value])]
    }

main :: IO ()
main = pureRuntime myHandler

Instances

Instances details
Eq ProxyResponse Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

Show ProxyResponse Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

Generic ProxyResponse Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

Associated Types

type Rep ProxyResponse :: Type -> Type #

ToJSON ProxyResponse Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

FromJSON ProxyResponse Source #

Since: 0.4.8

Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

type Rep ProxyResponse Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

type Rep ProxyResponse = D1 ('MetaData "ProxyResponse" "AWS.Lambda.Events.ApiGateway.ProxyResponse" "hal-0.4.8-40gZLn9f3jS82UCkewY0zs" 'False) (C1 ('MetaCons "ProxyResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: (S1 ('MetaSel ('Just "multiValueHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap (CI Text) [Text])) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProxyBody))))

response :: Status -> ProxyBody -> ProxyResponse Source #

Smart constructor for creating a ProxyResponse from a status and a body

addHeader :: Text -> Text -> ProxyResponse -> ProxyResponse Source #

Add a header to the ProxyResponse. If there was already a value for this header, this one is added, meaning the response will include multiple copies of this header (valid by the HTTP spec). This does NOT replace any previous headers or their values.

setHeader :: Text -> Text -> ProxyResponse -> ProxyResponse Source #

Set a header to the ProxyResponse. If there were any previous values for this header they are all replaced by this new value.

data ProxyBody Source #

Type that represents the body returned to an API Gateway when using HTTP Lambda Proxy integration. It is highly recommended that you do not use this type directly, and instead use the smart constructors exposed such as textPlain, applicationJson, and genericBinary. These make sure that the base64 encodings work transparently.

Constructors

ProxyBody 

Instances

Instances details
Eq ProxyBody Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

Show ProxyBody Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

Generic ProxyBody Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

Associated Types

type Rep ProxyBody :: Type -> Type #

type Rep ProxyBody Source # 
Instance details

Defined in AWS.Lambda.Events.ApiGateway.ProxyResponse

type Rep ProxyBody = D1 ('MetaData "ProxyBody" "AWS.Lambda.Events.ApiGateway.ProxyResponse" "hal-0.4.8-40gZLn9f3jS82UCkewY0zs" 'False) (C1 ('MetaCons "ProxyBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "contentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "serialized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "isBase64Encoded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

textPlain :: Text -> ProxyBody Source #

Smart constructor for creating a simple body of text.

applicationJson :: ToJSON a => a -> ProxyBody Source #

Smart constructor for creating a simple body of JSON.

genericBinary :: Text -> ByteString -> ProxyBody Source #

Smart constructor for creating a ProxyBody with an arbitrary ByteString of the chosen content type. Use this smart constructor to avoid invalid JSON representations of binary data.

From here it is easy to make more specific body constructors:

imageGif :: ByteString -> ProxyBody
imageGif = genericBinary "image/gif"

imageJpeg :: ByteString -> ProxyBody
imageJpeg = genericBinary "image/jpeg"

networkAuthenticationRequired511 :: Status #

Network Authentication Required 511 (RFC 6585)

status511 :: Status #

Network Authentication Required 511 (RFC 6585)

httpVersionNotSupported505 :: Status #

HTTP Version Not Supported 505

status505 :: Status #

HTTP Version Not Supported 505

gatewayTimeout504 :: Status #

Gateway Timeout 504

status504 :: Status #

Gateway Timeout 504

serviceUnavailable503 :: Status #

Service Unavailable 503

status503 :: Status #

Service Unavailable 503

badGateway502 :: Status #

Bad Gateway 502

status502 :: Status #

Bad Gateway 502

notImplemented501 :: Status #

Not Implemented 501

status501 :: Status #

Not Implemented 501

internalServerError500 :: Status #

Internal Server Error 500

status500 :: Status #

Internal Server Error 500

requestHeaderFieldsTooLarge431 :: Status #

Request Header Fields Too Large 431 (RFC 6585)

status431 :: Status #

Request Header Fields Too Large 431 (RFC 6585)

tooManyRequests429 :: Status #

Too Many Requests 429 (RFC 6585)

status429 :: Status #

Too Many Requests 429 (RFC 6585)

preconditionRequired428 :: Status #

Precondition Required 428 (RFC 6585)

status428 :: Status #

Precondition Required 428 (RFC 6585)

unprocessableEntity422 :: Status #

Unprocessable Entity 422 (RFC 4918)

status422 :: Status #

Unprocessable Entity 422 (RFC 4918)

imATeapot418 :: Status #

I'm a teapot 418

status418 :: Status #

I'm a teapot 418

expectationFailed417 :: Status #

Expectation Failed 417

status417 :: Status #

Expectation Failed 417

requestedRangeNotSatisfiable416 :: Status #

Requested Range Not Satisfiable 416

status416 :: Status #

Requested Range Not Satisfiable 416

unsupportedMediaType415 :: Status #

Unsupported Media Type 415

status415 :: Status #

Unsupported Media Type 415

requestURITooLong414 :: Status #

Request-URI Too Long 414

status414 :: Status #

Request-URI Too Long 414

requestEntityTooLarge413 :: Status #

Request Entity Too Large 413

status413 :: Status #

Request Entity Too Large 413

preconditionFailed412 :: Status #

Precondition Failed 412

status412 :: Status #

Precondition Failed 412

lengthRequired411 :: Status #

Length Required 411

status411 :: Status #

Length Required 411

gone410 :: Status #

Gone 410

status410 :: Status #

Gone 410

conflict409 :: Status #

Conflict 409

status409 :: Status #

Conflict 409

requestTimeout408 :: Status #

Request Timeout 408

status408 :: Status #

Request Timeout 408

proxyAuthenticationRequired407 :: Status #

Proxy Authentication Required 407

status407 :: Status #

Proxy Authentication Required 407

notAcceptable406 :: Status #

Not Acceptable 406

status406 :: Status #

Not Acceptable 406

methodNotAllowed405 :: Status #

Method Not Allowed 405

status405 :: Status #

Method Not Allowed 405

notFound404 :: Status #

Not Found 404

status404 :: Status #

Not Found 404

forbidden403 :: Status #

Forbidden 403

status403 :: Status #

Forbidden 403

paymentRequired402 :: Status #

Payment Required 402

status402 :: Status #

Payment Required 402

unauthorized401 :: Status #

Unauthorized 401

status401 :: Status #

Unauthorized 401

badRequest400 :: Status #

Bad Request 400

status400 :: Status #

Bad Request 400

permanentRedirect308 :: Status #

Permanent Redirect 308

status308 :: Status #

Permanent Redirect 308

temporaryRedirect307 :: Status #

Temporary Redirect 307

status307 :: Status #

Temporary Redirect 307

useProxy305 :: Status #

Use Proxy 305

status305 :: Status #

Use Proxy 305

notModified304 :: Status #

Not Modified 304

status304 :: Status #

Not Modified 304

seeOther303 :: Status #

See Other 303

status303 :: Status #

See Other 303

found302 :: Status #

Found 302

status302 :: Status #

Found 302

movedPermanently301 :: Status #

Moved Permanently 301

status301 :: Status #

Moved Permanently 301

multipleChoices300 :: Status #

Multiple Choices 300

status300 :: Status #

Multiple Choices 300

partialContent206 :: Status #

Partial Content 206

status206 :: Status #

Partial Content 206

resetContent205 :: Status #

Reset Content 205

status205 :: Status #

Reset Content 205

noContent204 :: Status #

No Content 204

status204 :: Status #

No Content 204

nonAuthoritative203 :: Status #

Non-Authoritative Information 203

status203 :: Status #

Non-Authoritative Information 203

accepted202 :: Status #

Accepted 202

status202 :: Status #

Accepted 202

created201 :: Status #

Created 201

status201 :: Status #

Created 201

ok200 :: Status #

OK 200

status200 :: Status #

OK 200

switchingProtocols101 :: Status #

Switching Protocols 101

status101 :: Status #

Switching Protocols 101

continue100 :: Status #

Continue 100

status100 :: Status #

Continue 100

data Status #

HTTP Status.

Only the statusCode is used for comparisons.

Please use mkStatus to create status codes from code and message, or the Enum instance or the status code constants (like ok200). There might be additional record members in the future.

Note that the Show instance is only for debugging.

Constructors

Status 

Instances

Instances details
Bounded Status 
Instance details

Defined in Network.HTTP.Types.Status

Enum Status 
Instance details

Defined in Network.HTTP.Types.Status

Eq Status 
Instance details

Defined in Network.HTTP.Types.Status

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Ord Status 
Instance details

Defined in Network.HTTP.Types.Status

Show Status 
Instance details

Defined in Network.HTTP.Types.Status