aws-lambda-haskell-runtime-4.3.2: Haskell runtime for AWS Lambda
Safe HaskellSafe-Inferred
LanguageHaskell2010

Aws.Lambda

Synopsis

Documentation

data Handler (handlerType :: HandlerType) m context request response error where Source #

Constructors

StandaloneLambdaHandler :: StandaloneCallback m context request response error -> Handler 'StandaloneHandlerType m context request response error 
APIGatewayHandler :: APIGatewayCallback m context request response error -> Handler 'APIGatewayHandlerType m context request response error 
ALBHandler :: ALBCallback m context request response error -> Handler 'ALBHandlerType m context request response error 

type Handlers handlerType m context request response error = HashMap HandlerName (Handler handlerType m context request response error) Source #

run :: RuntimeContext handlerType m context request response error => DispatcherOptions -> (forall a. m a -> IO a) -> Handlers handlerType m context request response error -> LambdaOptions context -> IO (Either (LambdaError handlerType) (LambdaResult handlerType)) Source #

addStandaloneLambdaHandler :: HandlerName -> StandaloneCallback m context request response error -> HandlersM 'StandaloneHandlerType m context request response error () Source #

addAPIGatewayHandler :: HandlerName -> APIGatewayCallback m context request response error -> HandlersM 'APIGatewayHandlerType m context request response error () Source #

addALBHandler :: HandlerName -> ALBCallback m context request response error -> HandlersM 'ALBHandlerType m context request response error () Source #

runLambdaHaskellRuntime :: RuntimeContext handlerType m context request response error => DispatcherOptions -> IO context -> (forall a. m a -> IO a) -> HandlersM handlerType m context request response error () -> IO () Source #

data Context context Source #

Context that is passed to all the handlers

initialize :: IORef context -> IO (Context context) Source #

Initializes the context out of the environment

setEventData :: Context context -> Event -> IO (Context context) Source #

Sets the context's event data

newtype DispatcherOptions Source #

Options that the dispatcher generator expects

type RunCallback (handlerType :: HandlerType) context = LambdaOptions context -> IO (Either (LambdaError handlerType) (LambdaResult handlerType)) Source #

Callback that we pass to the dispatcher function

data LambdaOptions context Source #

Options that the generated main expects

Instances

Instances details
Generic (LambdaOptions context) Source # 
Instance details

Defined in Aws.Lambda.Runtime.Common

Associated Types

type Rep (LambdaOptions context) :: Type -> Type #

Methods

from :: LambdaOptions context -> Rep (LambdaOptions context) x #

to :: Rep (LambdaOptions context) x -> LambdaOptions context #

type Rep (LambdaOptions context) Source # 
Instance details

Defined in Aws.Lambda.Runtime.Common

type Rep (LambdaOptions context) = D1 ('MetaData "LambdaOptions" "Aws.Lambda.Runtime.Common" "aws-lambda-haskell-runtime-4.3.2-LAPNpLFUvdgBtro5Sulqfh" 'False) (C1 ('MetaCons "LambdaOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "eventObject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawEventObject) :*: S1 ('MetaSel ('Just "functionHandler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HandlerName)) :*: (S1 ('MetaSel ('Just "executionUuid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "contextObject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Context context)))))

newtype ApiGatewayDispatcherOptions Source #

API Gateway specific dispatcher options

Constructors

ApiGatewayDispatcherOptions 

Fields

data HandlerType Source #

The type of the handler depending on how you proxy the Lambda

type RawEventObject = ByteString Source #

The event received by the lambda before any processing

data ApiGatewayRequest body Source #

data ApiGatewayResponse body Source #

Instances

Instances details
Functor ApiGatewayResponse Source # 
Instance details

Defined in Aws.Lambda.Runtime.APIGateway.Types

ToJSON body => ToJSON (ApiGatewayResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.APIGateway.Types

Generic (ApiGatewayResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.APIGateway.Types

Associated Types

type Rep (ApiGatewayResponse body) :: Type -> Type #

Show body => Show (ApiGatewayResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.APIGateway.Types

type Rep (ApiGatewayResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.APIGateway.Types

type Rep (ApiGatewayResponse body) = D1 ('MetaData "ApiGatewayResponse" "Aws.Lambda.Runtime.APIGateway.Types" "aws-lambda-haskell-runtime-4.3.2-LAPNpLFUvdgBtro5Sulqfh" 'False) (C1 ('MetaCons "ApiGatewayResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "apiGatewayResponseStatusCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "apiGatewayResponseHeaders") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ResponseHeaders)) :*: (S1 ('MetaSel ('Just "apiGatewayResponseBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 body) :*: S1 ('MetaSel ('Just "apiGatewayResponseIsBase64Encoded") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))

newtype ApiGatewayDispatcherOptions Source #

API Gateway specific dispatcher options

Constructors

ApiGatewayDispatcherOptions 

Fields

data ALBResponse body Source #

Instances

Instances details
Functor ALBResponse Source # 
Instance details

Defined in Aws.Lambda.Runtime.ALB.Types

Methods

fmap :: (a -> b) -> ALBResponse a -> ALBResponse b #

(<$) :: a -> ALBResponse b -> ALBResponse a #

ToJSON body => ToJSON (ALBResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.ALB.Types

Generic (ALBResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.ALB.Types

Associated Types

type Rep (ALBResponse body) :: Type -> Type #

Methods

from :: ALBResponse body -> Rep (ALBResponse body) x #

to :: Rep (ALBResponse body) x -> ALBResponse body #

Show body => Show (ALBResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.ALB.Types

Methods

showsPrec :: Int -> ALBResponse body -> ShowS #

show :: ALBResponse body -> String #

showList :: [ALBResponse body] -> ShowS #

type Rep (ALBResponse body) Source # 
Instance details

Defined in Aws.Lambda.Runtime.ALB.Types

type Rep (ALBResponse body) = D1 ('MetaData "ALBResponse" "Aws.Lambda.Runtime.ALB.Types" "aws-lambda-haskell-runtime-4.3.2-LAPNpLFUvdgBtro5Sulqfh" 'False) (C1 ('MetaCons "ALBResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "albResponseStatusCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "albResponseStatusDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "albResponseHeaders") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ResponseHeaders))) :*: (S1 ('MetaSel ('Just "albResponseMultiValueHeaders") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ResponseHeaders) :*: (S1 ('MetaSel ('Just "albResponseBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 body) :*: S1 ('MetaSel ('Just "albResponseIsBase64Encoded") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))))

mkALBResponse :: Int -> ResponseHeaders -> payload -> ALBResponse payload Source #

runLambda :: forall context handlerType. IO context -> RunCallback handlerType context -> IO () Source #

Runs the user haskell_lambda executable and posts back the results. This is called from the layer's main function.

newtype ApiGatewayDispatcherOptions Source #

API Gateway specific dispatcher options

Constructors

ApiGatewayDispatcherOptions 

Fields