serverless-haskell-0.12.5: Deploying Haskell code onto AWS Lambda using Serverless
Safe HaskellNone
LanguageHaskell2010

AWSLambda.Events.SQSEvent

Description

 
Synopsis

Documentation

data SQSMessage body Source #

Instances

Instances details
Eq body => Eq (SQSMessage body) Source # 
Instance details

Defined in AWSLambda.Events.SQSEvent

Methods

(==) :: SQSMessage body -> SQSMessage body -> Bool #

(/=) :: SQSMessage body -> SQSMessage body -> Bool #

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

Defined in AWSLambda.Events.SQSEvent

Methods

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

show :: SQSMessage body -> String #

showList :: [SQSMessage body] -> ShowS #

Generic (SQSMessage body) Source # 
Instance details

Defined in AWSLambda.Events.SQSEvent

Associated Types

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

Methods

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

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

FromText message => FromJSON (SQSMessage message) Source # 
Instance details

Defined in AWSLambda.Events.SQSEvent

Methods

parseJSON :: Value -> Parser (SQSMessage message) #

parseJSONList :: Value -> Parser [SQSMessage message] #

type Rep (SQSMessage body) Source # 
Instance details

Defined in AWSLambda.Events.SQSEvent

type Rep (SQSMessage body) = D1 ('MetaData "SQSMessage" "AWSLambda.Events.SQSEvent" "serverless-haskell-0.12.5-KjCqfdgbJz7IYIOcNfc9Yo" 'False) (C1 ('MetaCons "SQSMessage" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_sqsmMessageId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "_sqsmReceiptHandle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "_sqsmBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TextValue body)) :*: S1 ('MetaSel ('Just "_sqsmAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap Text Text)))) :*: ((S1 ('MetaSel ('Just "_sqsmMessageAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap Text MessageAttribute)) :*: S1 ('MetaSel ('Just "_sqsmMd5OfBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "_sqsmEventSource") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_sqsmEventSourceARN") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "_sqsmAwsRegion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Region))))))

sqsmMessageId :: forall body. Lens' (SQSMessage body) Text Source #

sqsmMd5OfBody :: forall body. Lens' (SQSMessage body) Text Source #

sqsmEventSource :: forall body. Lens' (SQSMessage body) Text Source #

sqsmBody :: forall body body. Lens (SQSMessage body) (SQSMessage body) (TextValue body) (TextValue body) Source #

sqsmAwsRegion :: forall body. Lens' (SQSMessage body) Region Source #

sqsMessages :: Traversal (SQSEvent message) (SQSEvent message') message message' Source #

A Traversal to get messages from an SQSEvent

sqsEmbedded :: Traversal (SQSEvent (Embedded v)) (SQSEvent (Embedded v')) v v' Source #

A Traversal to get embedded JSON values from an SQSEvent

traverseSqs :: (FromJSON a, Applicative m) => (a -> m ()) -> SQSEvent (Embedded a) -> m () Source #

Traverse all the messages in an SQS event

sqsMain :: (FromJSON a, MonadCatch m, MonadIO m) => (a -> m ()) -> m () Source #

A specialised version of the lambdaMain entry-point for handling individual SQS messages