{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

module AWSLambda.Events.Records where

import           Control.Exception.Safe (MonadCatch)
import           Control.Lens.TH (makeLenses)
import           Control.Monad.IO.Class
import           Data.Aeson (FromJSON(..), withObject, (.:))
import           Data.Foldable (traverse_)

import           AWSLambda.Handler (lambdaMain)

newtype RecordsEvent a = RecordsEvent { RecordsEvent a -> [a]
_reRecords :: [a] } deriving (RecordsEvent a -> RecordsEvent a -> Bool
(RecordsEvent a -> RecordsEvent a -> Bool)
-> (RecordsEvent a -> RecordsEvent a -> Bool)
-> Eq (RecordsEvent a)
forall a. Eq a => RecordsEvent a -> RecordsEvent a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecordsEvent a -> RecordsEvent a -> Bool
$c/= :: forall a. Eq a => RecordsEvent a -> RecordsEvent a -> Bool
== :: RecordsEvent a -> RecordsEvent a -> Bool
$c== :: forall a. Eq a => RecordsEvent a -> RecordsEvent a -> Bool
Eq, Int -> RecordsEvent a -> ShowS
[RecordsEvent a] -> ShowS
RecordsEvent a -> String
(Int -> RecordsEvent a -> ShowS)
-> (RecordsEvent a -> String)
-> ([RecordsEvent a] -> ShowS)
-> Show (RecordsEvent a)
forall a. Show a => Int -> RecordsEvent a -> ShowS
forall a. Show a => [RecordsEvent a] -> ShowS
forall a. Show a => RecordsEvent a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecordsEvent a] -> ShowS
$cshowList :: forall a. Show a => [RecordsEvent a] -> ShowS
show :: RecordsEvent a -> String
$cshow :: forall a. Show a => RecordsEvent a -> String
showsPrec :: Int -> RecordsEvent a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> RecordsEvent a -> ShowS
Show, a -> RecordsEvent b -> RecordsEvent a
(a -> b) -> RecordsEvent a -> RecordsEvent b
(forall a b. (a -> b) -> RecordsEvent a -> RecordsEvent b)
-> (forall a b. a -> RecordsEvent b -> RecordsEvent a)
-> Functor RecordsEvent
forall a b. a -> RecordsEvent b -> RecordsEvent a
forall a b. (a -> b) -> RecordsEvent a -> RecordsEvent b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> RecordsEvent b -> RecordsEvent a
$c<$ :: forall a b. a -> RecordsEvent b -> RecordsEvent a
fmap :: (a -> b) -> RecordsEvent a -> RecordsEvent b
$cfmap :: forall a b. (a -> b) -> RecordsEvent a -> RecordsEvent b
Functor, RecordsEvent a -> Bool
(a -> m) -> RecordsEvent a -> m
(a -> b -> b) -> b -> RecordsEvent a -> b
(forall m. Monoid m => RecordsEvent m -> m)
-> (forall m a. Monoid m => (a -> m) -> RecordsEvent a -> m)
-> (forall m a. Monoid m => (a -> m) -> RecordsEvent a -> m)
-> (forall a b. (a -> b -> b) -> b -> RecordsEvent a -> b)
-> (forall a b. (a -> b -> b) -> b -> RecordsEvent a -> b)
-> (forall b a. (b -> a -> b) -> b -> RecordsEvent a -> b)
-> (forall b a. (b -> a -> b) -> b -> RecordsEvent a -> b)
-> (forall a. (a -> a -> a) -> RecordsEvent a -> a)
-> (forall a. (a -> a -> a) -> RecordsEvent a -> a)
-> (forall a. RecordsEvent a -> [a])
-> (forall a. RecordsEvent a -> Bool)
-> (forall a. RecordsEvent a -> Int)
-> (forall a. Eq a => a -> RecordsEvent a -> Bool)
-> (forall a. Ord a => RecordsEvent a -> a)
-> (forall a. Ord a => RecordsEvent a -> a)
-> (forall a. Num a => RecordsEvent a -> a)
-> (forall a. Num a => RecordsEvent a -> a)
-> Foldable RecordsEvent
forall a. Eq a => a -> RecordsEvent a -> Bool
forall a. Num a => RecordsEvent a -> a
forall a. Ord a => RecordsEvent a -> a
forall m. Monoid m => RecordsEvent m -> m
forall a. RecordsEvent a -> Bool
forall a. RecordsEvent a -> Int
forall a. RecordsEvent a -> [a]
forall a. (a -> a -> a) -> RecordsEvent a -> a
forall m a. Monoid m => (a -> m) -> RecordsEvent a -> m
forall b a. (b -> a -> b) -> b -> RecordsEvent a -> b
forall a b. (a -> b -> b) -> b -> RecordsEvent a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: RecordsEvent a -> a
$cproduct :: forall a. Num a => RecordsEvent a -> a
sum :: RecordsEvent a -> a
$csum :: forall a. Num a => RecordsEvent a -> a
minimum :: RecordsEvent a -> a
$cminimum :: forall a. Ord a => RecordsEvent a -> a
maximum :: RecordsEvent a -> a
$cmaximum :: forall a. Ord a => RecordsEvent a -> a
elem :: a -> RecordsEvent a -> Bool
$celem :: forall a. Eq a => a -> RecordsEvent a -> Bool
length :: RecordsEvent a -> Int
$clength :: forall a. RecordsEvent a -> Int
null :: RecordsEvent a -> Bool
$cnull :: forall a. RecordsEvent a -> Bool
toList :: RecordsEvent a -> [a]
$ctoList :: forall a. RecordsEvent a -> [a]
foldl1 :: (a -> a -> a) -> RecordsEvent a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> RecordsEvent a -> a
foldr1 :: (a -> a -> a) -> RecordsEvent a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> RecordsEvent a -> a
foldl' :: (b -> a -> b) -> b -> RecordsEvent a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> RecordsEvent a -> b
foldl :: (b -> a -> b) -> b -> RecordsEvent a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> RecordsEvent a -> b
foldr' :: (a -> b -> b) -> b -> RecordsEvent a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> RecordsEvent a -> b
foldr :: (a -> b -> b) -> b -> RecordsEvent a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> RecordsEvent a -> b
foldMap' :: (a -> m) -> RecordsEvent a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> RecordsEvent a -> m
foldMap :: (a -> m) -> RecordsEvent a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> RecordsEvent a -> m
fold :: RecordsEvent m -> m
$cfold :: forall m. Monoid m => RecordsEvent m -> m
Foldable)

instance FromJSON a => FromJSON (RecordsEvent a) where
  parseJSON :: Value -> Parser (RecordsEvent a)
parseJSON = String
-> (Object -> Parser (RecordsEvent a))
-> Value
-> Parser (RecordsEvent a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RecordsEvent" ((Object -> Parser (RecordsEvent a))
 -> Value -> Parser (RecordsEvent a))
-> (Object -> Parser (RecordsEvent a))
-> Value
-> Parser (RecordsEvent a)
forall a b. (a -> b) -> a -> b
$ \Object
o -> [a] -> RecordsEvent a
forall a. [a] -> RecordsEvent a
RecordsEvent ([a] -> RecordsEvent a) -> Parser [a] -> Parser (RecordsEvent a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [a]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Records"

$(makeLenses ''RecordsEvent)

-- | Traverse all the records in a Lambda event
traverseRecords :: Applicative m => (a -> m ()) -> RecordsEvent a -> m ()
traverseRecords :: (a -> m ()) -> RecordsEvent a -> m ()
traverseRecords = (a -> m ()) -> RecordsEvent a -> m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_

-- | A specialised version of the 'lambdaMain' entry-point
-- for handling individual records in a Lambda event
recordsMain :: (FromJSON a, MonadCatch m, MonadIO m) => (a -> m ()) -> m ()
recordsMain :: (a -> m ()) -> m ()
recordsMain = (RecordsEvent a -> m ()) -> m ()
forall event res (m :: * -> *).
(FromJSON event, ToJSON res, MonadCatch m, MonadIO m) =>
(event -> m res) -> m ()
lambdaMain ((RecordsEvent a -> m ()) -> m ())
-> ((a -> m ()) -> RecordsEvent a -> m ()) -> (a -> m ()) -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> m ()) -> RecordsEvent a -> m ()
forall (m :: * -> *) a.
Applicative m =>
(a -> m ()) -> RecordsEvent a -> m ()
traverseRecords