{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
module AWSLambda.Events.APIGateway where
import Control.Lens hiding ((.=))
import Data.Aeson
import Data.Aeson.Casing (aesonDrop, camelCase)
import Data.Aeson.TH (deriveFromJSON)
import Data.Aeson.Embedded
import Data.Aeson.TextValue
import Data.Aeson.Types (Parser)
import Data.ByteString (ByteString)
import qualified Data.CaseInsensitive as CI
import Data.Function (on)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.IP
import qualified Data.Set as Set
import qualified Data.Text as Text
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import GHC.Generics (Generic)
import Network.AWS.Data.Base64
import Network.AWS.Data.Text
import qualified Network.HTTP.Types as HTTP
import Text.Read
import AWSLambda.Handler (lambdaMain)
type Method = Text
type = Text
type = Text
type QueryParamName = Text
type QueryParamValue = Text
type PathParamName = Text
type PathParamValue = Text
type StageVarName = Text
type StageVarValue = Text
data RequestIdentity = RequestIdentity
{ RequestIdentity -> Maybe Text
_riCognitoIdentityPoolId :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riAccountId :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riCognitoIdentityId :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riCaller :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riApiKey :: !(Maybe Text)
, RequestIdentity -> Maybe IP
_riSourceIp :: !(Maybe IP)
, RequestIdentity -> Maybe Text
_riCognitoAuthenticationType :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riCognitoAuthenticationProvider :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riUserArn :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riUserAgent :: !(Maybe Text)
, RequestIdentity -> Maybe Text
_riUser :: !(Maybe Text)
} deriving (RequestIdentity -> RequestIdentity -> Bool
(RequestIdentity -> RequestIdentity -> Bool)
-> (RequestIdentity -> RequestIdentity -> Bool)
-> Eq RequestIdentity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestIdentity -> RequestIdentity -> Bool
$c/= :: RequestIdentity -> RequestIdentity -> Bool
== :: RequestIdentity -> RequestIdentity -> Bool
$c== :: RequestIdentity -> RequestIdentity -> Bool
Eq, Int -> RequestIdentity -> ShowS
[RequestIdentity] -> ShowS
RequestIdentity -> String
(Int -> RequestIdentity -> ShowS)
-> (RequestIdentity -> String)
-> ([RequestIdentity] -> ShowS)
-> Show RequestIdentity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestIdentity] -> ShowS
$cshowList :: [RequestIdentity] -> ShowS
show :: RequestIdentity -> String
$cshow :: RequestIdentity -> String
showsPrec :: Int -> RequestIdentity -> ShowS
$cshowsPrec :: Int -> RequestIdentity -> ShowS
Show)
readParse :: Read a => String -> Text -> Parser a
readParse :: String -> Text -> Parser a
readParse String
msg Text
str =
case String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe (Text -> String
Text.unpack Text
str) of
Just a
result -> a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
result
Maybe a
Nothing -> String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser a) -> String -> Parser a
forall a b. (a -> b) -> a -> b
$ String
"Failed to parse an " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
instance FromJSON RequestIdentity where
parseJSON :: Value -> Parser RequestIdentity
parseJSON =
String
-> (Object -> Parser RequestIdentity)
-> Value
-> Parser RequestIdentity
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RequestIdentity" ((Object -> Parser RequestIdentity)
-> Value -> Parser RequestIdentity)
-> (Object -> Parser RequestIdentity)
-> Value
-> Parser RequestIdentity
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity
RequestIdentity (Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"cognitoIdentityPoolId" Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"accountId" Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"cognitoIdentityId" Parser
(Maybe Text
-> Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"caller" Parser
(Maybe Text
-> Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
-> Parser (Maybe Text)
-> Parser
(Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"apiKey" Parser
(Maybe IP
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
-> Parser (Maybe IP)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
(Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"sourceIp" Parser (Maybe Text)
-> (Maybe Text -> Parser (Maybe IP)) -> Parser (Maybe IP)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Text -> Parser IP) -> Maybe Text -> Parser (Maybe IP)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (String -> Text -> Parser IP
forall a. Read a => String -> Text -> Parser a
readParse String
"IP address")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> RequestIdentity)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text -> Maybe Text -> Maybe Text -> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"cognitoAuthenticationType" Parser
(Maybe Text
-> Maybe Text -> Maybe Text -> Maybe Text -> RequestIdentity)
-> Parser (Maybe Text)
-> Parser
(Maybe Text -> Maybe Text -> Maybe Text -> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"cognitoAuthenticationProvider" Parser (Maybe Text -> Maybe Text -> Maybe Text -> RequestIdentity)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Text -> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"userArn" Parser (Maybe Text -> Maybe Text -> RequestIdentity)
-> Parser (Maybe Text) -> Parser (Maybe Text -> RequestIdentity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"userAgent" Parser (Maybe Text -> RequestIdentity)
-> Parser (Maybe Text) -> Parser RequestIdentity
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"user"
$(makeLenses ''RequestIdentity)
data Authorizer = Authorizer
{ Authorizer -> Maybe Text
_aPrincipalId :: !(Maybe Text)
, Authorizer -> Object
_aClaims :: !Object
, Authorizer -> Object
_aContext :: !Object
} deriving (Authorizer -> Authorizer -> Bool
(Authorizer -> Authorizer -> Bool)
-> (Authorizer -> Authorizer -> Bool) -> Eq Authorizer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Authorizer -> Authorizer -> Bool
$c/= :: Authorizer -> Authorizer -> Bool
== :: Authorizer -> Authorizer -> Bool
$c== :: Authorizer -> Authorizer -> Bool
Eq, Int -> Authorizer -> ShowS
[Authorizer] -> ShowS
Authorizer -> String
(Int -> Authorizer -> ShowS)
-> (Authorizer -> String)
-> ([Authorizer] -> ShowS)
-> Show Authorizer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Authorizer] -> ShowS
$cshowList :: [Authorizer] -> ShowS
show :: Authorizer -> String
$cshow :: Authorizer -> String
showsPrec :: Int -> Authorizer -> ShowS
$cshowsPrec :: Int -> Authorizer -> ShowS
Show)
instance FromJSON Authorizer where
parseJSON :: Value -> Parser Authorizer
parseJSON = String
-> (Object -> Parser Authorizer) -> Value -> Parser Authorizer
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Authorizer" ((Object -> Parser Authorizer) -> Value -> Parser Authorizer)
-> (Object -> Parser Authorizer) -> Value -> Parser Authorizer
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Maybe Text -> Object -> Object -> Authorizer
Authorizer
(Maybe Text -> Object -> Object -> Authorizer)
-> Parser (Maybe Text) -> Parser (Object -> Object -> Authorizer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"principalId"
Parser (Object -> Object -> Authorizer)
-> Parser Object -> Parser (Object -> Authorizer)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"claims" Parser (Maybe Object) -> Object -> Parser Object
forall a. Parser (Maybe a) -> a -> Parser a
.!= Object
forall a. Monoid a => a
mempty
Parser (Object -> Authorizer) -> Parser Object -> Parser Authorizer
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object -> Parser Object
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Object -> Parser Object) -> Object -> Parser Object
forall a b. (a -> b) -> a -> b
$ Text -> Object -> Object
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
HashMap.delete Text
"principalId" (Object -> Object) -> Object -> Object
forall a b. (a -> b) -> a -> b
$ Text -> Object -> Object
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
HashMap.delete Text
"claims" Object
o)
$(makeLenses ''Authorizer)
data ProxyRequestContext = ProxyRequestContext
{ ProxyRequestContext -> Maybe Text
_prcPath :: !(Maybe Text)
, ProxyRequestContext -> Text
_prcAccountId :: !Text
, ProxyRequestContext -> Text
_prcResourceId :: !Text
, ProxyRequestContext -> Text
_prcStage :: !Text
, ProxyRequestContext -> Text
_prcRequestId :: !Text
, ProxyRequestContext -> RequestIdentity
_prcIdentity :: !RequestIdentity
, ProxyRequestContext -> Text
_prcResourcePath :: !Text
, ProxyRequestContext -> Text
_prcHttpMethod :: !Text
, ProxyRequestContext -> Text
_prcApiId :: !Text
, ProxyRequestContext -> Text
_prcProtocol :: !Text
, ProxyRequestContext -> Maybe Authorizer
_prcAuthorizer :: !(Maybe Authorizer)
} deriving (ProxyRequestContext -> ProxyRequestContext -> Bool
(ProxyRequestContext -> ProxyRequestContext -> Bool)
-> (ProxyRequestContext -> ProxyRequestContext -> Bool)
-> Eq ProxyRequestContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProxyRequestContext -> ProxyRequestContext -> Bool
$c/= :: ProxyRequestContext -> ProxyRequestContext -> Bool
== :: ProxyRequestContext -> ProxyRequestContext -> Bool
$c== :: ProxyRequestContext -> ProxyRequestContext -> Bool
Eq, Int -> ProxyRequestContext -> ShowS
[ProxyRequestContext] -> ShowS
ProxyRequestContext -> String
(Int -> ProxyRequestContext -> ShowS)
-> (ProxyRequestContext -> String)
-> ([ProxyRequestContext] -> ShowS)
-> Show ProxyRequestContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProxyRequestContext] -> ShowS
$cshowList :: [ProxyRequestContext] -> ShowS
show :: ProxyRequestContext -> String
$cshow :: ProxyRequestContext -> String
showsPrec :: Int -> ProxyRequestContext -> ShowS
$cshowsPrec :: Int -> ProxyRequestContext -> ShowS
Show)
$(deriveFromJSON (aesonDrop 4 camelCase) ''ProxyRequestContext)
$(makeLenses ''ProxyRequestContext)
data APIGatewayProxyRequest body = APIGatewayProxyRequest
{ APIGatewayProxyRequest body -> Text
_agprqResource :: !Text
, APIGatewayProxyRequest body -> ByteString
_agprqPath :: !ByteString
, APIGatewayProxyRequest body -> ByteString
_agprqHttpMethod :: !HTTP.Method
, :: !HTTP.RequestHeaders
, APIGatewayProxyRequest body -> Query
_agprqQueryStringParameters :: !HTTP.Query
, APIGatewayProxyRequest body -> HashMap Text Text
_agprqPathParameters :: !(HashMap PathParamName PathParamValue)
, APIGatewayProxyRequest body -> HashMap Text Text
_agprqStageVariables :: !(HashMap StageVarName StageVarValue)
, APIGatewayProxyRequest body -> ProxyRequestContext
_agprqRequestContext :: !ProxyRequestContext
, APIGatewayProxyRequest body -> Maybe (TextValue body)
_agprqBody :: !(Maybe (TextValue body))
} deriving (Int -> APIGatewayProxyRequest body -> ShowS
[APIGatewayProxyRequest body] -> ShowS
APIGatewayProxyRequest body -> String
(Int -> APIGatewayProxyRequest body -> ShowS)
-> (APIGatewayProxyRequest body -> String)
-> ([APIGatewayProxyRequest body] -> ShowS)
-> Show (APIGatewayProxyRequest body)
forall body.
Show body =>
Int -> APIGatewayProxyRequest body -> ShowS
forall body. Show body => [APIGatewayProxyRequest body] -> ShowS
forall body. Show body => APIGatewayProxyRequest body -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [APIGatewayProxyRequest body] -> ShowS
$cshowList :: forall body. Show body => [APIGatewayProxyRequest body] -> ShowS
show :: APIGatewayProxyRequest body -> String
$cshow :: forall body. Show body => APIGatewayProxyRequest body -> String
showsPrec :: Int -> APIGatewayProxyRequest body -> ShowS
$cshowsPrec :: forall body.
Show body =>
Int -> APIGatewayProxyRequest body -> ShowS
Show, (forall x.
APIGatewayProxyRequest body -> Rep (APIGatewayProxyRequest body) x)
-> (forall x.
Rep (APIGatewayProxyRequest body) x -> APIGatewayProxyRequest body)
-> Generic (APIGatewayProxyRequest body)
forall x.
Rep (APIGatewayProxyRequest body) x -> APIGatewayProxyRequest body
forall x.
APIGatewayProxyRequest body -> Rep (APIGatewayProxyRequest body) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall body x.
Rep (APIGatewayProxyRequest body) x -> APIGatewayProxyRequest body
forall body x.
APIGatewayProxyRequest body -> Rep (APIGatewayProxyRequest body) x
$cto :: forall body x.
Rep (APIGatewayProxyRequest body) x -> APIGatewayProxyRequest body
$cfrom :: forall body x.
APIGatewayProxyRequest body -> Rep (APIGatewayProxyRequest body) x
Generic)
instance Eq body => Eq (APIGatewayProxyRequest body) where
== :: APIGatewayProxyRequest body -> APIGatewayProxyRequest body -> Bool
(==) =
(Text, ByteString, ByteString, Set Header, Query,
HashMap Text Text, HashMap Text Text, ProxyRequestContext,
Maybe (TextValue body))
-> (Text, ByteString, ByteString, Set Header, Query,
HashMap Text Text, HashMap Text Text, ProxyRequestContext,
Maybe (TextValue body))
-> Bool
forall a. Eq a => a -> a -> Bool
(==) ((Text, ByteString, ByteString, Set Header, Query,
HashMap Text Text, HashMap Text Text, ProxyRequestContext,
Maybe (TextValue body))
-> (Text, ByteString, ByteString, Set Header, Query,
HashMap Text Text, HashMap Text Text, ProxyRequestContext,
Maybe (TextValue body))
-> Bool)
-> (APIGatewayProxyRequest body
-> (Text, ByteString, ByteString, Set Header, Query,
HashMap Text Text, HashMap Text Text, ProxyRequestContext,
Maybe (TextValue body)))
-> APIGatewayProxyRequest body
-> APIGatewayProxyRequest body
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` \APIGatewayProxyRequest body
rq ->
( APIGatewayProxyRequest body -> Text
forall body. APIGatewayProxyRequest body -> Text
_agprqResource APIGatewayProxyRequest body
rq
, APIGatewayProxyRequest body -> ByteString
forall body. APIGatewayProxyRequest body -> ByteString
_agprqPath APIGatewayProxyRequest body
rq
, APIGatewayProxyRequest body -> ByteString
forall body. APIGatewayProxyRequest body -> ByteString
_agprqHttpMethod APIGatewayProxyRequest body
rq
, RequestHeaders -> Set Header
forall a. Ord a => [a] -> Set a
Set.fromList (APIGatewayProxyRequest body -> RequestHeaders
forall body. APIGatewayProxyRequest body -> RequestHeaders
_agprqHeaders APIGatewayProxyRequest body
rq)
, APIGatewayProxyRequest body -> Query
forall body. APIGatewayProxyRequest body -> Query
_agprqQueryStringParameters APIGatewayProxyRequest body
rq
, APIGatewayProxyRequest body -> HashMap Text Text
forall body. APIGatewayProxyRequest body -> HashMap Text Text
_agprqPathParameters APIGatewayProxyRequest body
rq
, APIGatewayProxyRequest body -> HashMap Text Text
forall body. APIGatewayProxyRequest body -> HashMap Text Text
_agprqStageVariables APIGatewayProxyRequest body
rq
, APIGatewayProxyRequest body -> ProxyRequestContext
forall body. APIGatewayProxyRequest body -> ProxyRequestContext
_agprqRequestContext APIGatewayProxyRequest body
rq
, APIGatewayProxyRequest body -> Maybe (TextValue body)
forall body. APIGatewayProxyRequest body -> Maybe (TextValue body)
_agprqBody APIGatewayProxyRequest body
rq)
instance FromText body => FromJSON (APIGatewayProxyRequest body) where
parseJSON :: Value -> Parser (APIGatewayProxyRequest body)
parseJSON = String
-> (Object -> Parser (APIGatewayProxyRequest body))
-> Value
-> Parser (APIGatewayProxyRequest body)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"APIGatewayProxyRequest" ((Object -> Parser (APIGatewayProxyRequest body))
-> Value -> Parser (APIGatewayProxyRequest body))
-> (Object -> Parser (APIGatewayProxyRequest body))
-> Value
-> Parser (APIGatewayProxyRequest body)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Text
-> ByteString
-> ByteString
-> RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body
forall body.
Text
-> ByteString
-> ByteString
-> RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body
APIGatewayProxyRequest
(Text
-> ByteString
-> ByteString
-> RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
-> Parser Text
-> Parser
(ByteString
-> ByteString
-> RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"resource"
Parser
(ByteString
-> ByteString
-> RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
-> Parser ByteString
-> Parser
(ByteString
-> RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Parser Text -> Parser ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"path")
Parser
(ByteString
-> RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
-> Parser ByteString
-> Parser
(RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Parser Text -> Parser ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"httpMethod")
Parser
(RequestHeaders
-> Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
-> Parser RequestHeaders
-> Parser
(Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((HashMap Text Text -> RequestHeaders)
-> Maybe (HashMap Text Text) -> Maybe RequestHeaders
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HashMap Text Text -> RequestHeaders
fromAWSHeaders (Maybe (HashMap Text Text) -> Maybe RequestHeaders)
-> Parser (Maybe (HashMap Text Text))
-> Parser (Maybe RequestHeaders)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"headers") Parser (Maybe RequestHeaders)
-> RequestHeaders -> Parser RequestHeaders
forall a. Parser (Maybe a) -> a -> Parser a
.!= RequestHeaders
forall a. Monoid a => a
mempty
Parser
(Query
-> HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
-> Parser Query
-> Parser
(HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((HashMap Text Text -> Query)
-> Maybe (HashMap Text Text) -> Maybe Query
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HashMap Text Text -> Query
fromAWSQuery (Maybe (HashMap Text Text) -> Maybe Query)
-> Parser (Maybe (HashMap Text Text)) -> Parser (Maybe Query)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"queryStringParameters") Parser (Maybe Query) -> Query -> Parser Query
forall a. Parser (Maybe a) -> a -> Parser a
.!= Query
forall a. Monoid a => a
mempty
Parser
(HashMap Text Text
-> HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
-> Parser (HashMap Text Text)
-> Parser
(HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"pathParameters" Parser (Maybe (HashMap Text Text))
-> HashMap Text Text -> Parser (HashMap Text Text)
forall a. Parser (Maybe a) -> a -> Parser a
.!= HashMap Text Text
forall k v. HashMap k v
HashMap.empty
Parser
(HashMap Text Text
-> ProxyRequestContext
-> Maybe (TextValue body)
-> APIGatewayProxyRequest body)
-> Parser (HashMap Text Text)
-> Parser
(ProxyRequestContext
-> Maybe (TextValue body) -> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"stageVariables" Parser (Maybe (HashMap Text Text))
-> HashMap Text Text -> Parser (HashMap Text Text)
forall a. Parser (Maybe a) -> a -> Parser a
.!= HashMap Text Text
forall k v. HashMap k v
HashMap.empty
Parser
(ProxyRequestContext
-> Maybe (TextValue body) -> APIGatewayProxyRequest body)
-> Parser ProxyRequestContext
-> Parser (Maybe (TextValue body) -> APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser ProxyRequestContext
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"requestContext"
Parser (Maybe (TextValue body) -> APIGatewayProxyRequest body)
-> Parser (Maybe (TextValue body))
-> Parser (APIGatewayProxyRequest body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe (TextValue body))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"body"
where
fromAWSHeaders :: HashMap HeaderName HeaderValue -> HTTP.RequestHeaders
fromAWSHeaders :: HashMap Text Text -> RequestHeaders
fromAWSHeaders = ((Text, Text) -> Header) -> [(Text, Text)] -> RequestHeaders
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Text) -> Header
toHeader ([(Text, Text)] -> RequestHeaders)
-> (HashMap Text Text -> [(Text, Text)])
-> HashMap Text Text
-> RequestHeaders
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Text Text -> [(Text, Text)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList
where
toHeader :: (Text, Text) -> Header
toHeader = (Text -> CI ByteString)
-> (Text -> ByteString) -> (Text, Text) -> Header
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (ByteString -> CI ByteString
forall s. FoldCase s => s -> CI s
CI.mk (ByteString -> CI ByteString)
-> (Text -> ByteString) -> Text -> CI ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8) Text -> ByteString
encodeUtf8
fromAWSQuery :: HashMap QueryParamName QueryParamValue -> HTTP.Query
fromAWSQuery :: HashMap Text Text -> Query
fromAWSQuery = ((Text, Text) -> (ByteString, Maybe ByteString))
-> [(Text, Text)] -> Query
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Text) -> (ByteString, Maybe ByteString)
toQueryItem ([(Text, Text)] -> Query)
-> (HashMap Text Text -> [(Text, Text)])
-> HashMap Text Text
-> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Text Text -> [(Text, Text)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList
where
toQueryItem :: (Text, Text) -> (ByteString, Maybe ByteString)
toQueryItem = (Text -> ByteString)
-> (Text -> Maybe ByteString)
-> (Text, Text)
-> (ByteString, Maybe ByteString)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> ByteString
encodeUtf8 (\Text
x -> if Text -> Bool
Text.null Text
x then Maybe ByteString
forall a. Maybe a
Nothing else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Text -> ByteString) -> Text -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> Maybe ByteString) -> Text -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text
x)
$()
requestBody :: Getter (APIGatewayProxyRequest body) (Maybe body)
requestBody :: (Maybe body -> f (Maybe body))
-> APIGatewayProxyRequest body -> f (APIGatewayProxyRequest body)
requestBody = (Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> APIGatewayProxyRequest body -> f (APIGatewayProxyRequest body)
forall body body.
Lens
(APIGatewayProxyRequest body)
(APIGatewayProxyRequest body)
(Maybe (TextValue body))
(Maybe (TextValue body))
agprqBody ((Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> APIGatewayProxyRequest body -> f (APIGatewayProxyRequest body))
-> ((Maybe body -> f (Maybe body))
-> Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> (Maybe body -> f (Maybe body))
-> APIGatewayProxyRequest body
-> f (APIGatewayProxyRequest body)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso (TextValue body) (TextValue body) body body
-> Iso
(Maybe (TextValue body))
(Maybe (TextValue body))
(Maybe body)
(Maybe body)
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping AnIso (TextValue body) (TextValue body) body body
forall a1 a2. Iso (TextValue a1) (TextValue a2) a1 a2
unTextValue
requestBodyEmbedded :: Getter (APIGatewayProxyRequest (Embedded v)) (Maybe v)
requestBodyEmbedded :: (Maybe v -> f (Maybe v))
-> APIGatewayProxyRequest (Embedded v)
-> f (APIGatewayProxyRequest (Embedded v))
requestBodyEmbedded = (Maybe (Embedded v) -> f (Maybe (Embedded v)))
-> APIGatewayProxyRequest (Embedded v)
-> f (APIGatewayProxyRequest (Embedded v))
forall body. Getter (APIGatewayProxyRequest body) (Maybe body)
requestBody ((Maybe (Embedded v) -> f (Maybe (Embedded v)))
-> APIGatewayProxyRequest (Embedded v)
-> f (APIGatewayProxyRequest (Embedded v)))
-> ((Maybe v -> f (Maybe v))
-> Maybe (Embedded v) -> f (Maybe (Embedded v)))
-> (Maybe v -> f (Maybe v))
-> APIGatewayProxyRequest (Embedded v)
-> f (APIGatewayProxyRequest (Embedded v))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso (Embedded v) (Embedded v) v v
-> Iso
(Maybe (Embedded v)) (Maybe (Embedded v)) (Maybe v) (Maybe v)
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping AnIso (Embedded v) (Embedded v) v v
forall a1 a2. Iso (Embedded a1) (Embedded a2) a1 a2
unEmbed
requestBodyBinary :: Getter (APIGatewayProxyRequest Base64) (Maybe ByteString)
requestBodyBinary :: (Maybe ByteString -> f (Maybe ByteString))
-> APIGatewayProxyRequest Base64
-> f (APIGatewayProxyRequest Base64)
requestBodyBinary = (Maybe Base64 -> f (Maybe Base64))
-> APIGatewayProxyRequest Base64
-> f (APIGatewayProxyRequest Base64)
forall body. Getter (APIGatewayProxyRequest body) (Maybe body)
requestBody ((Maybe Base64 -> f (Maybe Base64))
-> APIGatewayProxyRequest Base64
-> f (APIGatewayProxyRequest Base64))
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe Base64 -> f (Maybe Base64))
-> (Maybe ByteString -> f (Maybe ByteString))
-> APIGatewayProxyRequest Base64
-> f (APIGatewayProxyRequest Base64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso Base64 Base64 ByteString ByteString
-> Iso
(Maybe Base64) (Maybe Base64) (Maybe ByteString) (Maybe ByteString)
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping AnIso Base64 Base64 ByteString ByteString
Iso' Base64 ByteString
_Base64
data APIGatewayProxyResponse body = APIGatewayProxyResponse
{ :: !Int
, :: !HTTP.ResponseHeaders
, APIGatewayProxyResponse body -> Maybe (TextValue body)
_agprsBody :: !(Maybe (TextValue body))
} deriving (Int -> APIGatewayProxyResponse body -> ShowS
[APIGatewayProxyResponse body] -> ShowS
APIGatewayProxyResponse body -> String
(Int -> APIGatewayProxyResponse body -> ShowS)
-> (APIGatewayProxyResponse body -> String)
-> ([APIGatewayProxyResponse body] -> ShowS)
-> Show (APIGatewayProxyResponse body)
forall body.
Show body =>
Int -> APIGatewayProxyResponse body -> ShowS
forall body. Show body => [APIGatewayProxyResponse body] -> ShowS
forall body. Show body => APIGatewayProxyResponse body -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [APIGatewayProxyResponse body] -> ShowS
$cshowList :: forall body. Show body => [APIGatewayProxyResponse body] -> ShowS
show :: APIGatewayProxyResponse body -> String
$cshow :: forall body. Show body => APIGatewayProxyResponse body -> String
showsPrec :: Int -> APIGatewayProxyResponse body -> ShowS
$cshowsPrec :: forall body.
Show body =>
Int -> APIGatewayProxyResponse body -> ShowS
Show, (forall x.
APIGatewayProxyResponse body
-> Rep (APIGatewayProxyResponse body) x)
-> (forall x.
Rep (APIGatewayProxyResponse body) x
-> APIGatewayProxyResponse body)
-> Generic (APIGatewayProxyResponse body)
forall x.
Rep (APIGatewayProxyResponse body) x
-> APIGatewayProxyResponse body
forall x.
APIGatewayProxyResponse body
-> Rep (APIGatewayProxyResponse body) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall body x.
Rep (APIGatewayProxyResponse body) x
-> APIGatewayProxyResponse body
forall body x.
APIGatewayProxyResponse body
-> Rep (APIGatewayProxyResponse body) x
$cto :: forall body x.
Rep (APIGatewayProxyResponse body) x
-> APIGatewayProxyResponse body
$cfrom :: forall body x.
APIGatewayProxyResponse body
-> Rep (APIGatewayProxyResponse body) x
Generic)
instance (Eq body) => Eq (APIGatewayProxyResponse body) where
== :: APIGatewayProxyResponse body
-> APIGatewayProxyResponse body -> Bool
(==) = (Int, Set Header, Maybe (TextValue body))
-> (Int, Set Header, Maybe (TextValue body)) -> Bool
forall a. Eq a => a -> a -> Bool
(==) ((Int, Set Header, Maybe (TextValue body))
-> (Int, Set Header, Maybe (TextValue body)) -> Bool)
-> (APIGatewayProxyResponse body
-> (Int, Set Header, Maybe (TextValue body)))
-> APIGatewayProxyResponse body
-> APIGatewayProxyResponse body
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` \APIGatewayProxyResponse body
r -> (APIGatewayProxyResponse body -> Int
forall body. APIGatewayProxyResponse body -> Int
_agprsStatusCode APIGatewayProxyResponse body
r, RequestHeaders -> Set Header
forall a. Ord a => [a] -> Set a
Set.fromList (APIGatewayProxyResponse body -> RequestHeaders
forall body. APIGatewayProxyResponse body -> RequestHeaders
_agprsHeaders APIGatewayProxyResponse body
r), APIGatewayProxyResponse body -> Maybe (TextValue body)
forall body. APIGatewayProxyResponse body -> Maybe (TextValue body)
_agprsBody APIGatewayProxyResponse body
r)
instance ToText body => ToJSON (APIGatewayProxyResponse body) where
toJSON :: APIGatewayProxyResponse body -> Value
toJSON APIGatewayProxyResponse {Int
RequestHeaders
Maybe (TextValue body)
_agprsBody :: Maybe (TextValue body)
_agprsHeaders :: RequestHeaders
_agprsStatusCode :: Int
_agprsBody :: forall body. APIGatewayProxyResponse body -> Maybe (TextValue body)
_agprsHeaders :: forall body. APIGatewayProxyResponse body -> RequestHeaders
_agprsStatusCode :: forall body. APIGatewayProxyResponse body -> Int
..} =
[Pair] -> Value
object
[ Text
"statusCode" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int
_agprsStatusCode
, Text
"headers" Text -> HashMap Text Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestHeaders -> HashMap Text Text
toAWSHeaders RequestHeaders
_agprsHeaders
, Text
"body" Text -> Maybe (TextValue body) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe (TextValue body)
_agprsBody
]
where
toAWSHeaders :: HTTP.ResponseHeaders -> HashMap HeaderName HeaderValue
toAWSHeaders :: RequestHeaders -> HashMap Text Text
toAWSHeaders = [(Text, Text)] -> HashMap Text Text
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(Text, Text)] -> HashMap Text Text)
-> (RequestHeaders -> [(Text, Text)])
-> RequestHeaders
-> HashMap Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Header -> (Text, Text)) -> RequestHeaders -> [(Text, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CI ByteString -> Text)
-> (ByteString -> Text) -> Header -> (Text, Text)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (ByteString -> Text
decodeUtf8 (ByteString -> Text)
-> (CI ByteString -> ByteString) -> CI ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CI ByteString -> ByteString
forall s. CI s -> s
CI.original) ByteString -> Text
decodeUtf8)
instance FromText body => FromJSON (APIGatewayProxyResponse body) where
parseJSON :: Value -> Parser (APIGatewayProxyResponse body)
parseJSON =
String
-> (Object -> Parser (APIGatewayProxyResponse body))
-> Value
-> Parser (APIGatewayProxyResponse body)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"APIGatewayProxyResponse" ((Object -> Parser (APIGatewayProxyResponse body))
-> Value -> Parser (APIGatewayProxyResponse body))
-> (Object -> Parser (APIGatewayProxyResponse body))
-> Value
-> Parser (APIGatewayProxyResponse body)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Int
-> RequestHeaders
-> Maybe (TextValue body)
-> APIGatewayProxyResponse body
forall body.
Int
-> RequestHeaders
-> Maybe (TextValue body)
-> APIGatewayProxyResponse body
APIGatewayProxyResponse (Int
-> RequestHeaders
-> Maybe (TextValue body)
-> APIGatewayProxyResponse body)
-> Parser Int
-> Parser
(RequestHeaders
-> Maybe (TextValue body) -> APIGatewayProxyResponse body)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"statusCode" Parser
(RequestHeaders
-> Maybe (TextValue body) -> APIGatewayProxyResponse body)
-> Parser RequestHeaders
-> Parser (Maybe (TextValue body) -> APIGatewayProxyResponse body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
(HashMap Text Text -> RequestHeaders
fromAWSHeaders (HashMap Text Text -> RequestHeaders)
-> Parser (HashMap Text Text) -> Parser RequestHeaders
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (HashMap Text Text)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"headers") Parser (Maybe (TextValue body) -> APIGatewayProxyResponse body)
-> Parser (Maybe (TextValue body))
-> Parser (APIGatewayProxyResponse body)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o Object -> Text -> Parser (Maybe (TextValue body))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"body"
where
fromAWSHeaders :: HashMap HeaderName HeaderValue -> HTTP.RequestHeaders
fromAWSHeaders :: HashMap Text Text -> RequestHeaders
fromAWSHeaders = ((Text, Text) -> Header) -> [(Text, Text)] -> RequestHeaders
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Text) -> Header
toHeader ([(Text, Text)] -> RequestHeaders)
-> (HashMap Text Text -> [(Text, Text)])
-> HashMap Text Text
-> RequestHeaders
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Text Text -> [(Text, Text)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList
where
toHeader :: (Text, Text) -> Header
toHeader = (Text -> CI ByteString)
-> (Text -> ByteString) -> (Text, Text) -> Header
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (ByteString -> CI ByteString
forall s. FoldCase s => s -> CI s
CI.mk (ByteString -> CI ByteString)
-> (Text -> ByteString) -> Text -> CI ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8) Text -> ByteString
encodeUtf8
$()
response :: Int -> APIGatewayProxyResponse body
response :: Int -> APIGatewayProxyResponse body
response Int
statusCode = Int
-> RequestHeaders
-> Maybe (TextValue body)
-> APIGatewayProxyResponse body
forall body.
Int
-> RequestHeaders
-> Maybe (TextValue body)
-> APIGatewayProxyResponse body
APIGatewayProxyResponse Int
statusCode RequestHeaders
forall a. Monoid a => a
mempty Maybe (TextValue body)
forall a. Maybe a
Nothing
responseOK :: APIGatewayProxyResponse body
responseOK :: APIGatewayProxyResponse body
responseOK = Int -> APIGatewayProxyResponse body
forall body. Int -> APIGatewayProxyResponse body
response Int
200
responseNotFound :: APIGatewayProxyResponse body
responseNotFound :: APIGatewayProxyResponse body
responseNotFound = Int -> APIGatewayProxyResponse body
forall body. Int -> APIGatewayProxyResponse body
response Int
404
responseBadRequest :: APIGatewayProxyResponse body
responseBadRequest :: APIGatewayProxyResponse body
responseBadRequest = Int -> APIGatewayProxyResponse body
forall body. Int -> APIGatewayProxyResponse body
response Int
400
responseBody :: Setter' (APIGatewayProxyResponse body) (Maybe body)
responseBody :: (Maybe body -> f (Maybe body))
-> APIGatewayProxyResponse body -> f (APIGatewayProxyResponse body)
responseBody = (Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> APIGatewayProxyResponse body -> f (APIGatewayProxyResponse body)
forall body body.
Lens
(APIGatewayProxyResponse body)
(APIGatewayProxyResponse body)
(Maybe (TextValue body))
(Maybe (TextValue body))
agprsBody ((Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> APIGatewayProxyResponse body
-> f (APIGatewayProxyResponse body))
-> ((Maybe body -> f (Maybe body))
-> Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> (Maybe body -> f (Maybe body))
-> APIGatewayProxyResponse body
-> f (APIGatewayProxyResponse body)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Maybe (TextValue body))
-> Lens'
(Maybe (TextValue body)) (Maybe (IxValue (Maybe (TextValue body))))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at () ((Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> ((Maybe body -> f (Maybe body))
-> Maybe (TextValue body) -> f (Maybe (TextValue body)))
-> (Maybe body -> f (Maybe body))
-> Maybe (TextValue body)
-> f (Maybe (TextValue body))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso (TextValue body) (TextValue body) body body
-> Iso
(Maybe (TextValue body))
(Maybe (TextValue body))
(Maybe body)
(Maybe body)
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping AnIso (TextValue body) (TextValue body) body body
forall a1 a2. Iso (TextValue a1) (TextValue a2) a1 a2
unTextValue
responseBodyEmbedded :: Setter' (APIGatewayProxyResponse (Embedded body)) (Maybe body)
responseBodyEmbedded :: (Maybe body -> f (Maybe body))
-> APIGatewayProxyResponse (Embedded body)
-> f (APIGatewayProxyResponse (Embedded body))
responseBodyEmbedded = (Maybe (Embedded body) -> f (Maybe (Embedded body)))
-> APIGatewayProxyResponse (Embedded body)
-> f (APIGatewayProxyResponse (Embedded body))
forall body. Setter' (APIGatewayProxyResponse body) (Maybe body)
responseBody ((Maybe (Embedded body) -> f (Maybe (Embedded body)))
-> APIGatewayProxyResponse (Embedded body)
-> f (APIGatewayProxyResponse (Embedded body)))
-> ((Maybe body -> f (Maybe body))
-> Maybe (Embedded body) -> f (Maybe (Embedded body)))
-> (Maybe body -> f (Maybe body))
-> APIGatewayProxyResponse (Embedded body)
-> f (APIGatewayProxyResponse (Embedded body))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso (Embedded body) (Embedded body) body body
-> Iso
(Maybe (Embedded body))
(Maybe (Embedded body))
(Maybe body)
(Maybe body)
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping AnIso (Embedded body) (Embedded body) body body
forall a1 a2. Iso (Embedded a1) (Embedded a2) a1 a2
unEmbed
responseBodyBinary :: Setter' (APIGatewayProxyResponse Base64) (Maybe ByteString)
responseBodyBinary :: (Maybe ByteString -> f (Maybe ByteString))
-> APIGatewayProxyResponse Base64
-> f (APIGatewayProxyResponse Base64)
responseBodyBinary = (Maybe Base64 -> f (Maybe Base64))
-> APIGatewayProxyResponse Base64
-> f (APIGatewayProxyResponse Base64)
forall body. Setter' (APIGatewayProxyResponse body) (Maybe body)
responseBody ((Maybe Base64 -> f (Maybe Base64))
-> APIGatewayProxyResponse Base64
-> f (APIGatewayProxyResponse Base64))
-> ((Maybe ByteString -> f (Maybe ByteString))
-> Maybe Base64 -> f (Maybe Base64))
-> (Maybe ByteString -> f (Maybe ByteString))
-> APIGatewayProxyResponse Base64
-> f (APIGatewayProxyResponse Base64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso Base64 Base64 ByteString ByteString
-> Iso
(Maybe Base64) (Maybe Base64) (Maybe ByteString) (Maybe ByteString)
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping AnIso Base64 Base64 ByteString ByteString
Iso' Base64 ByteString
_Base64
apiGatewayMain
:: (FromText reqBody, ToText resBody)
=> (APIGatewayProxyRequest reqBody -> IO (APIGatewayProxyResponse resBody))
-> IO ()
apiGatewayMain :: (APIGatewayProxyRequest reqBody
-> IO (APIGatewayProxyResponse resBody))
-> IO ()
apiGatewayMain = (APIGatewayProxyRequest reqBody
-> IO (APIGatewayProxyResponse resBody))
-> IO ()
forall event res (m :: * -> *).
(FromJSON event, ToJSON res, MonadCatch m, MonadIO m) =>
(event -> m res) -> m ()
lambdaMain