Safe Haskell | None |
---|---|
Language | Haskell2010 |
Aws.Lambda
Synopsis
- 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
- 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
- mkApiGatewayResponse :: Int -> payload -> ApiGatewayResponse payload
- data Context context = Context {
- memoryLimitInMb :: !Int
- functionName :: !String
- functionVersion :: !String
- invokedFunctionArn :: !String
- awsRequestId :: !String
- xrayTraceId :: !String
- logStreamName :: !String
- logGroupName :: !String
- deadline :: !Int
- customContext :: !(IORef context)
- initialize :: Throws Parsing => Throws EnvironmentVariableNotSet => IORef context -> IO (Context context)
- setEventData :: Context context -> Event -> IO (Context context)
- module Aws.Lambda.Runtime
- data LambdaOptions context = LambdaOptions {
- eventObject :: !ByteString
- functionHandler :: !String
- executionUuid :: !String
- contextObject :: !(Context context)
- generateLambdaDispatcher :: DispatcherStrategy -> DispatcherOptions -> DecsQ
- decodeObj :: forall a. (FromJSON a, Typeable a) => ByteString -> Either Parsing a
Documentation
data ApiGatewayRequest body Source #
Constructors
Instances
Show body => Show (ApiGatewayRequest body) Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods showsPrec :: Int -> ApiGatewayRequest body -> ShowS # show :: ApiGatewayRequest body -> String # showList :: [ApiGatewayRequest body] -> ShowS # | |
FromJSON body => FromJSON (ApiGatewayRequest body) Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods parseJSON :: Value -> Parser (ApiGatewayRequest body) # parseJSONList :: Value -> Parser [ApiGatewayRequest body] # | |
FromJSON (ApiGatewayRequest Text) Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods parseJSON :: Value -> Parser (ApiGatewayRequest Text) # parseJSONList :: Value -> Parser [ApiGatewayRequest Text] # | |
FromJSON (ApiGatewayRequest String) Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods parseJSON :: Value -> Parser (ApiGatewayRequest String) # parseJSONList :: Value -> Parser [ApiGatewayRequest String] # |
data ApiGatewayRequestContext Source #
Constructors
Instances
Show ApiGatewayRequestContext Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods showsPrec :: Int -> ApiGatewayRequestContext -> ShowS # show :: ApiGatewayRequestContext -> String # showList :: [ApiGatewayRequestContext] -> ShowS # | |
FromJSON ApiGatewayRequestContext Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods parseJSON :: Value -> Parser ApiGatewayRequestContext # parseJSONList :: Value -> Parser [ApiGatewayRequestContext] # |
data ApiGatewayRequestContextIdentity Source #
Constructors
Instances
Show ApiGatewayRequestContextIdentity Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods showsPrec :: Int -> ApiGatewayRequestContextIdentity -> ShowS # | |
FromJSON ApiGatewayRequestContextIdentity Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods parseJSON :: Value -> Parser ApiGatewayRequestContextIdentity # parseJSONList :: Value -> Parser [ApiGatewayRequestContextIdentity] # |
data ApiGatewayResponse body Source #
Constructors
ApiGatewayResponse | |
Fields |
Instances
newtype ApiGatewayResponseBody Source #
Constructors
ApiGatewayResponseBody Text |
Instances
ToJSON ApiGatewayResponseBody Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods toJSON :: ApiGatewayResponseBody -> Value # toEncoding :: ApiGatewayResponseBody -> Encoding # toJSONList :: [ApiGatewayResponseBody] -> Value # | |
FromJSON ApiGatewayResponseBody Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods parseJSON :: Value -> Parser ApiGatewayResponseBody # parseJSONList :: Value -> Parser [ApiGatewayResponseBody] # |
class ToApiGatewayResponseBody a where Source #
Methods
toApiGatewayResponseBody :: a -> ApiGatewayResponseBody Source #
Instances
ToJSON a => ToApiGatewayResponseBody a Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods toApiGatewayResponseBody :: a -> ApiGatewayResponseBody Source # | |
ToApiGatewayResponseBody Text Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods toApiGatewayResponseBody :: Text -> ApiGatewayResponseBody Source # | |
ToApiGatewayResponseBody String Source # | |
Defined in Aws.Lambda.Runtime.ApiGatewayInfo Methods toApiGatewayResponseBody :: String -> ApiGatewayResponseBody Source # |
mkApiGatewayResponse :: Int -> payload -> ApiGatewayResponse payload Source #
Context that is passed to all the handlers
Constructors
Context | |
Fields
|
initialize :: Throws Parsing => Throws EnvironmentVariableNotSet => 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
module Aws.Lambda.Runtime
data LambdaOptions context Source #
Options that the generated main expects
Constructors
LambdaOptions | |
Fields
|
Instances
Generic (LambdaOptions context) Source # | |
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 # | |
Defined in Aws.Lambda.Runtime.Common type Rep (LambdaOptions context) = D1 (MetaData "LambdaOptions" "Aws.Lambda.Runtime.Common" "aws-lambda-haskell-runtime-3.0.4-F2AcvwPeu267KQkcJuRIfl" False) (C1 (MetaCons "LambdaOptions" PrefixI True) ((S1 (MetaSel (Just "eventObject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Just "functionHandler") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) :*: (S1 (MetaSel (Just "executionUuid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String) :*: S1 (MetaSel (Just "contextObject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Context context))))) |
generateLambdaDispatcher :: DispatcherStrategy -> DispatcherOptions -> DecsQ Source #
Generates a main
function that acts as a dispatcher