Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Aws.Lambda
Synopsis
- data Handler (handlerType :: HandlerType) m context request response error where
- 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
- newtype HandlerName = HandlerName {}
- type Handlers handlerType m context request response error = HashMap HandlerName (Handler handlerType m context request response error)
- 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))
- addStandaloneLambdaHandler :: HandlerName -> StandaloneCallback m context request response error -> HandlersM 'StandaloneHandlerType m context request response error ()
- addAPIGatewayHandler :: HandlerName -> APIGatewayCallback m context request response error -> HandlersM 'APIGatewayHandlerType m context request response error ()
- addALBHandler :: HandlerName -> ALBCallback m context request response error -> HandlersM 'ALBHandlerType m context request response error ()
- 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 ()
- data Context context = Context {
- memoryLimitInMb :: !Int
- functionName :: !Text
- functionVersion :: !Text
- invokedFunctionArn :: !Text
- awsRequestId :: !Text
- xrayTraceId :: !Text
- logStreamName :: !Text
- logGroupName :: !Text
- deadline :: !Int
- customContext :: !(IORef context)
- initialize :: IORef context -> IO (Context context)
- setEventData :: Context context -> Event -> IO (Context context)
- newtype DispatcherOptions = DispatcherOptions {}
- defaultDispatcherOptions :: DispatcherOptions
- type RunCallback (handlerType :: HandlerType) context = LambdaOptions context -> IO (Either (LambdaError handlerType) (LambdaResult handlerType))
- data LambdaResult (handlerType :: HandlerType) where
- StandaloneLambdaResult :: StandaloneLambdaResponseBody -> LambdaResult 'StandaloneHandlerType
- APIGatewayResult :: ApiGatewayResponse ApiGatewayResponseBody -> LambdaResult 'APIGatewayHandlerType
- ALBResult :: ALBResponse ALBResponseBody -> LambdaResult 'ALBHandlerType
- data LambdaError (handlerType :: HandlerType) where
- StandaloneLambdaError :: StandaloneLambdaResponseBody -> LambdaError 'StandaloneHandlerType
- APIGatewayLambdaError :: ApiGatewayResponse ApiGatewayResponseBody -> LambdaError 'APIGatewayHandlerType
- ALBLambdaError :: ALBResponse ALBResponseBody -> LambdaError 'ALBHandlerType
- data LambdaOptions context = LambdaOptions {
- eventObject :: !RawEventObject
- functionHandler :: !HandlerName
- executionUuid :: !Text
- contextObject :: !(Context context)
- newtype ApiGatewayDispatcherOptions = ApiGatewayDispatcherOptions {}
- data HandlerType
- newtype HandlerName = HandlerName {}
- type RawEventObject = ByteString
- data ApiGatewayRequest body = ApiGatewayRequest {
- apiGatewayRequestResource :: !Text
- apiGatewayRequestPath :: !Text
- apiGatewayRequestHttpMethod :: !Text
- apiGatewayRequestHeaders :: !(Maybe (HashMap Text Text))
- apiGatewayRequestQueryStringParameters :: !(Maybe (HashMap Text Text))
- apiGatewayRequestPathParameters :: !(Maybe (HashMap Text Text))
- apiGatewayRequestStageVariables :: !(Maybe (HashMap Text Text))
- apiGatewayRequestIsBase64Encoded :: !Bool
- apiGatewayRequestRequestContext :: !ApiGatewayRequestContext
- apiGatewayRequestBody :: !(Maybe body)
- data ApiGatewayRequestContext = ApiGatewayRequestContext {
- apiGatewayRequestContextResourceId :: !Text
- apiGatewayRequestContextResourcePath :: !Text
- apiGatewayRequestContextHttpMethod :: !Text
- apiGatewayRequestContextExtendedRequestId :: !Text
- apiGatewayRequestContextRequestTime :: !Text
- apiGatewayRequestContextPath :: !Text
- apiGatewayRequestContextAccountId :: !Text
- apiGatewayRequestContextProtocol :: !Text
- apiGatewayRequestContextStage :: !Text
- apiGatewayRequestContextDomainPrefix :: !Text
- apiGatewayRequestContextRequestId :: !Text
- apiGatewayRequestContextDomainName :: !Text
- apiGatewayRequestContextApiId :: !Text
- apiGatewayRequestContextIdentity :: !ApiGatewayRequestContextIdentity
- apiGatewayRequestContextAuthorizer :: !(Maybe Value)
- data ApiGatewayRequestContextIdentity = ApiGatewayRequestContextIdentity {
- apiGatewayRequestContextIdentityCognitoIdentityPoolId :: !(Maybe Text)
- apiGatewayRequestContextIdentityAccountId :: !(Maybe Text)
- apiGatewayRequestContextIdentityCognitoIdentityId :: !(Maybe Text)
- apiGatewayRequestContextIdentityCaller :: !(Maybe Text)
- apiGatewayRequestContextIdentitySourceIp :: !(Maybe Text)
- apiGatewayRequestContextIdentityPrincipalOrgId :: !(Maybe Text)
- apiGatewayRequestContextIdentityAccesskey :: !(Maybe Text)
- apiGatewayRequestContextIdentityCognitoAuthenticationType :: !(Maybe Text)
- apiGatewayRequestContextIdentityCognitoAuthenticationProvider :: !(Maybe Value)
- apiGatewayRequestContextIdentityUserArn :: !(Maybe Text)
- apiGatewayRequestContextIdentityUserAgent :: !(Maybe Text)
- apiGatewayRequestContextIdentityUser :: !(Maybe Text)
- data ApiGatewayResponse body = ApiGatewayResponse {}
- newtype ApiGatewayResponseBody = ApiGatewayResponseBody Text
- class ToApiGatewayResponseBody a where
- newtype ApiGatewayDispatcherOptions = ApiGatewayDispatcherOptions {}
- mkApiGatewayResponse :: Int -> ResponseHeaders -> payload -> ApiGatewayResponse payload
- data ALBRequest body = ALBRequest {
- albRequestPath :: !Text
- albRequestHttpMethod :: !Text
- albRequestHeaders :: !(Maybe (HashMap Text Text))
- albRequestQueryStringParameters :: !(Maybe (HashMap Text Text))
- albRequestIsBase64Encoded :: !Bool
- albRequestRequestContext :: !ALBRequestContext
- albRequestBody :: !(Maybe body)
- newtype ALBRequestContext = ALBRequestContext {
- albRequestContextElb :: ALBELB
- data ALBResponse body = ALBResponse {}
- newtype ALBResponseBody = ALBResponseBody Text
- class ToALBResponseBody a where
- toALBResponseBody :: a -> ALBResponseBody
- mkALBResponse :: Int -> ResponseHeaders -> payload -> ALBResponse payload
- runLambda :: forall context handlerType. IO context -> RunCallback handlerType context -> IO ()
- data LambdaResult (handlerType :: HandlerType) where
- StandaloneLambdaResult :: StandaloneLambdaResponseBody -> LambdaResult 'StandaloneHandlerType
- APIGatewayResult :: ApiGatewayResponse ApiGatewayResponseBody -> LambdaResult 'APIGatewayHandlerType
- ALBResult :: ALBResponse ALBResponseBody -> LambdaResult 'ALBHandlerType
- newtype ApiGatewayDispatcherOptions = ApiGatewayDispatcherOptions {}
- data Parsing = Parsing {
- errorMessage :: Text
- actualValue :: Text
- valueName :: Text
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 |
newtype HandlerName Source #
A handler name used to configure the lambda in AWS
Constructors
HandlerName | |
Fields |
Instances
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 #
Context that is passed to all the handlers
Constructors
Context | |
Fields
|
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
Constructors
DispatcherOptions | |
type RunCallback (handlerType :: HandlerType) context = LambdaOptions context -> IO (Either (LambdaError handlerType) (LambdaResult handlerType)) Source #
Callback that we pass to the dispatcher function
data LambdaResult (handlerType :: HandlerType) where Source #
Wrapper type to handle the result of the user
Constructors
StandaloneLambdaResult :: StandaloneLambdaResponseBody -> LambdaResult 'StandaloneHandlerType | |
APIGatewayResult :: ApiGatewayResponse ApiGatewayResponseBody -> LambdaResult 'APIGatewayHandlerType | |
ALBResult :: ALBResponse ALBResponseBody -> LambdaResult 'ALBHandlerType |
data LambdaError (handlerType :: HandlerType) where Source #
Wrapper type for lambda execution results
Constructors
StandaloneLambdaError :: StandaloneLambdaResponseBody -> LambdaError 'StandaloneHandlerType | |
APIGatewayLambdaError :: ApiGatewayResponse ApiGatewayResponseBody -> LambdaError 'APIGatewayHandlerType | |
ALBLambdaError :: ALBResponse ALBResponseBody -> LambdaError 'ALBHandlerType |
data LambdaOptions context Source #
Options that the generated main expects
Constructors
LambdaOptions | |
Fields
|
Instances
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
Constructors
StandaloneHandlerType | |
APIGatewayHandlerType | |
ALBHandlerType |
newtype HandlerName Source #
A handler name used to configure the lambda in AWS
Constructors
HandlerName | |
Fields |
Instances
type RawEventObject = ByteString Source #
The event received by the lambda before any processing
data ApiGatewayRequest body Source #
Constructors
Instances
FromJSON (ApiGatewayRequest Text) Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods parseJSON :: Value -> Parser (ApiGatewayRequest Text) # parseJSONList :: Value -> Parser [ApiGatewayRequest Text] # | |
FromJSON (ApiGatewayRequest String) Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods parseJSON :: Value -> Parser (ApiGatewayRequest String) # parseJSONList :: Value -> Parser [ApiGatewayRequest String] # | |
FromJSON body => FromJSON (ApiGatewayRequest body) Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods parseJSON :: Value -> Parser (ApiGatewayRequest body) # parseJSONList :: Value -> Parser [ApiGatewayRequest body] # omittedField :: Maybe (ApiGatewayRequest body) # | |
Show body => Show (ApiGatewayRequest body) Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods showsPrec :: Int -> ApiGatewayRequest body -> ShowS # show :: ApiGatewayRequest body -> String # showList :: [ApiGatewayRequest body] -> ShowS # |
data ApiGatewayRequestContext Source #
Constructors
Instances
FromJSON ApiGatewayRequestContext Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods parseJSON :: Value -> Parser ApiGatewayRequestContext # parseJSONList :: Value -> Parser [ApiGatewayRequestContext] # | |
Show ApiGatewayRequestContext Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods showsPrec :: Int -> ApiGatewayRequestContext -> ShowS # show :: ApiGatewayRequestContext -> String # showList :: [ApiGatewayRequestContext] -> ShowS # |
data ApiGatewayRequestContextIdentity Source #
Constructors
Instances
data ApiGatewayResponse body Source #
Constructors
ApiGatewayResponse | |
Fields |
Instances
newtype ApiGatewayResponseBody Source #
Constructors
ApiGatewayResponseBody Text |
Instances
FromJSON ApiGatewayResponseBody Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods parseJSON :: Value -> Parser ApiGatewayResponseBody # parseJSONList :: Value -> Parser [ApiGatewayResponseBody] # | |
ToJSON ApiGatewayResponseBody Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods toJSON :: ApiGatewayResponseBody -> Value # toEncoding :: ApiGatewayResponseBody -> Encoding # toJSONList :: [ApiGatewayResponseBody] -> Value # toEncodingList :: [ApiGatewayResponseBody] -> Encoding # omitField :: ApiGatewayResponseBody -> Bool # |
class ToApiGatewayResponseBody a where Source #
Methods
toApiGatewayResponseBody :: a -> ApiGatewayResponseBody Source #
Instances
ToApiGatewayResponseBody Text Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods toApiGatewayResponseBody :: Text -> ApiGatewayResponseBody Source # | |
ToApiGatewayResponseBody String Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods toApiGatewayResponseBody :: String -> ApiGatewayResponseBody Source # | |
ToJSON a => ToApiGatewayResponseBody a Source # | |
Defined in Aws.Lambda.Runtime.APIGateway.Types Methods toApiGatewayResponseBody :: a -> ApiGatewayResponseBody Source # |
newtype ApiGatewayDispatcherOptions Source #
API Gateway specific dispatcher options
Constructors
ApiGatewayDispatcherOptions | |
Fields
|
mkApiGatewayResponse :: Int -> ResponseHeaders -> payload -> ApiGatewayResponse payload Source #
data ALBRequest body Source #
Constructors
ALBRequest | |
Fields
|
Instances
FromJSON (ALBRequest Text) Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods parseJSON :: Value -> Parser (ALBRequest Text) # parseJSONList :: Value -> Parser [ALBRequest Text] # omittedField :: Maybe (ALBRequest Text) # | |
FromJSON (ALBRequest String) Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods parseJSON :: Value -> Parser (ALBRequest String) # parseJSONList :: Value -> Parser [ALBRequest String] # omittedField :: Maybe (ALBRequest String) # | |
FromJSON body => FromJSON (ALBRequest body) Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods parseJSON :: Value -> Parser (ALBRequest body) # parseJSONList :: Value -> Parser [ALBRequest body] # omittedField :: Maybe (ALBRequest body) # | |
Show body => Show (ALBRequest body) Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods showsPrec :: Int -> ALBRequest body -> ShowS # show :: ALBRequest body -> String # showList :: [ALBRequest body] -> ShowS # |
newtype ALBRequestContext Source #
Constructors
ALBRequestContext | |
Fields
|
Instances
FromJSON ALBRequestContext Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods parseJSON :: Value -> Parser ALBRequestContext # parseJSONList :: Value -> Parser [ALBRequestContext] # | |
Show ALBRequestContext Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods showsPrec :: Int -> ALBRequestContext -> ShowS # show :: ALBRequestContext -> String # showList :: [ALBRequestContext] -> ShowS # |
data ALBResponse body Source #
Constructors
ALBResponse | |
Fields |
Instances
newtype ALBResponseBody Source #
Constructors
ALBResponseBody Text |
Instances
FromJSON ALBResponseBody Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods parseJSON :: Value -> Parser ALBResponseBody # parseJSONList :: Value -> Parser [ALBResponseBody] # | |
ToJSON ALBResponseBody Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods toJSON :: ALBResponseBody -> Value # toEncoding :: ALBResponseBody -> Encoding # toJSONList :: [ALBResponseBody] -> Value # toEncodingList :: [ALBResponseBody] -> Encoding # omitField :: ALBResponseBody -> Bool # |
class ToALBResponseBody a where Source #
Methods
toALBResponseBody :: a -> ALBResponseBody Source #
Instances
ToALBResponseBody Text Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods | |
ToALBResponseBody String Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods | |
ToJSON a => ToALBResponseBody a Source # | |
Defined in Aws.Lambda.Runtime.ALB.Types Methods toALBResponseBody :: a -> ALBResponseBody Source # |
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.
data LambdaResult (handlerType :: HandlerType) where Source #
Wrapper type to handle the result of the user
Constructors
StandaloneLambdaResult :: StandaloneLambdaResponseBody -> LambdaResult 'StandaloneHandlerType | |
APIGatewayResult :: ApiGatewayResponse ApiGatewayResponseBody -> LambdaResult 'APIGatewayHandlerType | |
ALBResult :: ALBResponse ALBResponseBody -> LambdaResult 'ALBHandlerType |
newtype ApiGatewayDispatcherOptions Source #
API Gateway specific dispatcher options
Constructors
ApiGatewayDispatcherOptions | |
Fields
|
Constructors
Parsing | |
Fields
|
Instances
ToJSON Parsing Source # | |
Exception Parsing Source # | |
Defined in Aws.Lambda.Runtime.Error Methods toException :: Parsing -> SomeException # fromException :: SomeException -> Maybe Parsing # displayException :: Parsing -> String # | |
Show Parsing Source # | |