{-|
Module      : AWS.Lambda.Events.ApiGateway.ProxyRequest
Description : Data types that represent typical lambda responses
Copyright   : (c) Nike, Inc., 2019
License     : BSD3
Maintainer  : nathan.fairhurst@nike.com, fernando.freire@nike.com
Stability   : stable

This module exposes types used to model incoming __proxy__ requests from AWS
API Gateway.  These types are a light pass over the incoming JSON
representation.
-}
module AWS.Lambda.Events.ApiGateway.ProxyRequest
    ( ProxyRequest(..)
    , RequestContext(..)
    , Identity(..)
    , NoAuthorizer
    , StrictlyNoAuthorizer
    ) where

import           Data.Aeson                  (FromJSON(..), ToJSON(..),
                                              Value(..), object, withObject,
                                              (.=), (.:), (.:?))
import           Data.ByteString.Base64.Lazy (decodeLenient, encode)
import           Data.ByteString.Lazy        (ByteString)
import           Data.CaseInsensitive        (CI, FoldCase, mk, original)
import           Data.Foldable               (fold)
import           Data.Hashable               (Hashable)
import           Data.HashMap.Strict         (HashMap, foldrWithKey, insert)
import           Data.Maybe                  (catMaybes)
import           Data.Text                   (Text)
import qualified Data.Text.Lazy              as TL
import qualified Data.Text.Lazy.Encoding     as TLE
import           Data.Void                   (Void)
import           GHC.Generics                (Generic (..))

-- This function is available in Data.Functor as of base 4.11, but we define it
-- here for compatibility.
(<&>) :: Functor f => f a -> (a -> b) -> f b
<&> :: f a -> (a -> b) -> f b
(<&>) f a
x a -> b
f = a -> b
f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
x

infixl 1 <&>

data Identity = Identity
    { Identity -> Maybe Text
cognitoIdentityPoolId         :: Maybe Text
    , Identity -> Maybe Text
accountId                     :: Maybe Text
    , Identity -> Maybe Text
cognitoIdentityId             :: Maybe Text
    , Identity -> Maybe Text
caller                        :: Maybe Text
    , Identity -> Maybe Text
apiKey                        :: Maybe Text
    , Identity -> Text
sourceIp                      :: Text
    , Identity -> Maybe Text
accessKey                     :: Maybe Text
    , Identity -> Maybe Text
cognitoAuthenticationType     :: Maybe Text
    , Identity -> Maybe Text
cognitoAuthenticationProvider :: Maybe Text
    , Identity -> Maybe Text
userArn                       :: Maybe Text
    , Identity -> Maybe Text
apiKeyId                      :: Maybe Text
    , Identity -> Maybe Text
userAgent                     :: Maybe Text
    , Identity -> Maybe Text
user                          :: Maybe Text
    } deriving (Identity -> Identity -> Bool
(Identity -> Identity -> Bool)
-> (Identity -> Identity -> Bool) -> Eq Identity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity -> Identity -> Bool
$c/= :: Identity -> Identity -> Bool
== :: Identity -> Identity -> Bool
$c== :: Identity -> Identity -> Bool
Eq, (forall x. Identity -> Rep Identity x)
-> (forall x. Rep Identity x -> Identity) -> Generic Identity
forall x. Rep Identity x -> Identity
forall x. Identity -> Rep Identity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Identity x -> Identity
$cfrom :: forall x. Identity -> Rep Identity x
Generic, Int -> Identity -> ShowS
[Identity] -> ShowS
Identity -> String
(Int -> Identity -> ShowS)
-> (Identity -> String) -> ([Identity] -> ShowS) -> Show Identity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity] -> ShowS
$cshowList :: [Identity] -> ShowS
show :: Identity -> String
$cshow :: Identity -> String
showsPrec :: Int -> Identity -> ShowS
$cshowsPrec :: Int -> Identity -> ShowS
Show)

instance FromJSON Identity
instance ToJSON Identity

data RequestContext a = RequestContext
    { RequestContext a -> Text
path              :: Text
    , RequestContext a -> Text
accountId         :: Text
    , RequestContext a -> Maybe a
authorizer        :: Maybe a
    , RequestContext a -> Text
resourceId        :: Text
    , RequestContext a -> Text
stage             :: Text
    , RequestContext a -> Maybe Text
domainPrefix      :: Maybe Text
    , RequestContext a -> Text
requestId         :: Text
    , RequestContext a -> Identity
identity          :: Identity
    , RequestContext a -> Maybe Text
domainName        :: Maybe Text
    , RequestContext a -> Text
resourcePath      :: Text
    , RequestContext a -> Text
httpMethod        :: Text
    , RequestContext a -> Maybe Text
extendedRequestId :: Maybe Text
    , RequestContext a -> Text
apiId             :: Text
    } deriving (RequestContext a -> RequestContext a -> Bool
(RequestContext a -> RequestContext a -> Bool)
-> (RequestContext a -> RequestContext a -> Bool)
-> Eq (RequestContext a)
forall a. Eq a => RequestContext a -> RequestContext a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestContext a -> RequestContext a -> Bool
$c/= :: forall a. Eq a => RequestContext a -> RequestContext a -> Bool
== :: RequestContext a -> RequestContext a -> Bool
$c== :: forall a. Eq a => RequestContext a -> RequestContext a -> Bool
Eq, (forall x. RequestContext a -> Rep (RequestContext a) x)
-> (forall x. Rep (RequestContext a) x -> RequestContext a)
-> Generic (RequestContext a)
forall x. Rep (RequestContext a) x -> RequestContext a
forall x. RequestContext a -> Rep (RequestContext a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (RequestContext a) x -> RequestContext a
forall a x. RequestContext a -> Rep (RequestContext a) x
$cto :: forall a x. Rep (RequestContext a) x -> RequestContext a
$cfrom :: forall a x. RequestContext a -> Rep (RequestContext a) x
Generic, Int -> RequestContext a -> ShowS
[RequestContext a] -> ShowS
RequestContext a -> String
(Int -> RequestContext a -> ShowS)
-> (RequestContext a -> String)
-> ([RequestContext a] -> ShowS)
-> Show (RequestContext a)
forall a. Show a => Int -> RequestContext a -> ShowS
forall a. Show a => [RequestContext a] -> ShowS
forall a. Show a => RequestContext a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestContext a] -> ShowS
$cshowList :: forall a. Show a => [RequestContext a] -> ShowS
show :: RequestContext a -> String
$cshow :: forall a. Show a => RequestContext a -> String
showsPrec :: Int -> RequestContext a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> RequestContext a -> ShowS
Show)

instance FromJSON a => FromJSON (RequestContext a) where
    parseJSON :: Value -> Parser (RequestContext a)
parseJSON = String
-> (Object -> Parser (RequestContext a))
-> Value
-> Parser (RequestContext a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ProxyRequest" ((Object -> Parser (RequestContext a))
 -> Value -> Parser (RequestContext a))
-> (Object -> Parser (RequestContext a))
-> Value
-> Parser (RequestContext a)
forall a b. (a -> b) -> a -> b
$ \Object
v ->
        Text
-> Text
-> Maybe a
-> Text
-> Text
-> Maybe Text
-> Text
-> Identity
-> Maybe Text
-> Text
-> Text
-> Maybe Text
-> Text
-> RequestContext a
forall a.
Text
-> Text
-> Maybe a
-> Text
-> Text
-> Maybe Text
-> Text
-> Identity
-> Maybe Text
-> Text
-> Text
-> Maybe Text
-> Text
-> RequestContext a
RequestContext (Text
 -> Text
 -> Maybe a
 -> Text
 -> Text
 -> Maybe Text
 -> Text
 -> Identity
 -> Maybe Text
 -> Text
 -> Text
 -> Maybe Text
 -> Text
 -> RequestContext a)
-> Parser Text
-> Parser
     (Text
      -> Maybe a
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Identity
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> RequestContext a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"path" Parser
  (Text
   -> Maybe a
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Identity
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> RequestContext a)
-> Parser Text
-> Parser
     (Maybe a
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Identity
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"accountId" Parser
  (Maybe a
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Identity
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> RequestContext a)
-> Parser (Maybe a)
-> Parser
     (Text
      -> Text
      -> Maybe Text
      -> Text
      -> Identity
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser (Maybe a)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"authorizer" Parser
  (Text
   -> Text
   -> Maybe Text
   -> Text
   -> Identity
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> RequestContext a)
-> Parser Text
-> Parser
     (Text
      -> Maybe Text
      -> Text
      -> Identity
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"resourceId" Parser
  (Text
   -> Maybe Text
   -> Text
   -> Identity
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> RequestContext a)
-> Parser Text
-> Parser
     (Maybe Text
      -> Text
      -> Identity
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"stage" Parser
  (Maybe Text
   -> Text
   -> Identity
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> RequestContext a)
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Identity
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"domainPrefix" Parser
  (Text
   -> Identity
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> RequestContext a)
-> Parser Text
-> Parser
     (Identity
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"requestId" Parser
  (Identity
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> RequestContext a)
-> Parser Identity
-> Parser
     (Maybe Text
      -> Text -> Text -> Maybe Text -> Text -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Identity
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"identity" Parser
  (Maybe Text
   -> Text -> Text -> Maybe Text -> Text -> RequestContext a)
-> Parser (Maybe Text)
-> Parser (Text -> Text -> Maybe Text -> Text -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"domainName" Parser (Text -> Text -> Maybe Text -> Text -> RequestContext a)
-> Parser Text
-> Parser (Text -> Maybe Text -> Text -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"resourcePath" Parser (Text -> Maybe Text -> Text -> RequestContext a)
-> Parser Text -> Parser (Maybe Text -> Text -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"httpMethod" Parser (Maybe Text -> Text -> RequestContext a)
-> Parser (Maybe Text) -> Parser (Text -> RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"extendedRequestId" Parser (Text -> RequestContext a)
-> Parser Text -> Parser (RequestContext a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"apiId"

-- | @since 0.4.8
instance ToJSON a => ToJSON (RequestContext a) where
    toJSON :: RequestContext a -> Value
toJSON RequestContext a
r = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes
        [ Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"path" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
path (RequestContext a
r :: RequestContext a)
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"accountId" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
accountId (RequestContext a
r :: RequestContext a)
        , (Text
"authorizer" Text -> a -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (a -> Pair) -> Maybe a -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RequestContext a -> Maybe a
forall a. RequestContext a -> Maybe a
authorizer RequestContext a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"resourceId" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
resourceId RequestContext a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"stage" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
stage RequestContext a
r
        , (Text
"domainPrefix" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RequestContext a -> Maybe Text
forall a. RequestContext a -> Maybe Text
domainPrefix RequestContext a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"requestId" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
requestId RequestContext a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"identity" Text -> Identity -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Identity
forall a. RequestContext a -> Identity
identity RequestContext a
r
        , (Text
"domainName" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RequestContext a -> Maybe Text
forall a. RequestContext a -> Maybe Text
domainName RequestContext a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"resourcePath" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
resourcePath RequestContext a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"httpMethod" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
httpMethod (RequestContext a
r :: RequestContext a)
        , (Text
"extendedRequestId" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RequestContext a -> Maybe Text
forall a. RequestContext a -> Maybe Text
extendedRequestId RequestContext a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"apiId" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RequestContext a -> Text
forall a. RequestContext a -> Text
apiId RequestContext a
r
        ]

-- TODO: Should also include websocket fields
-- | This type is for representing events that come from API Gateway via the
-- Lambda Proxy integration (forwarding HTTP data directly, rather than a
-- custom integration).  It will automatically decode the event that comes in.
--
-- The 'ProxyRequest' notably has one parameter for the type of information
-- returned by the API Gateway's custom authorizer (if applicable).  This type
-- must also implement FromJSON so that it can be decoded.  If you do not
-- expect this data to be populated we recommended using the 'NoAuthorizer'
-- type exported from this module (which is just an alias for 'Value').  If
-- there _must not_ be authorizer populated (this is unlikely) then use the
-- 'StrictlyNoAuthorizer' type.
--
-- @
--     {-\# LANGUAGE NamedFieldPuns \#-}
--     {-\# LANGUAGE DuplicateRecordFields \#-}
--
--     module Main where
--
--     import AWS.Lambda.Runtime (pureRuntime)
--     import AWS.Lambda.Events.ApiGateway.ProxyRequest (ProxyRequest(..), NoAuthorizer)
--     import AWS.Lambda.Events.ApiGateway.ProxyResponse (ProxyResponse(..), textPlain, forbidden403, ok200)
--
--     myHandler :: ProxyRequest NoAuthorizer -> ProxyResponse
--     myHandler ProxyRequest { httpMethod = \"GET\", path = "/say_hello" } =
--         ProxyResponse
--         {   status = ok200
--         ,   body = textPlain \"Hello\"
--         ,   headers = mempty
--         ,   multiValueHeaders = mempty
--         }
--     myHandler _ =
--         ProxyResponse
--         {   status = forbidden403
--         ,   body = textPlain \"Forbidden\"
--         ,   headers = mempty
--         ,   multiValueHeaders = mempty
--         }
--
--     main :: IO ()
--     main = pureRuntime myHandler
-- @
data ProxyRequest a = ProxyRequest
    { ProxyRequest a -> Text
path                            :: Text
    , ProxyRequest a -> HashMap (CI Text) Text
headers                         :: HashMap (CI Text) Text
    , ProxyRequest a -> HashMap (CI Text) [Text]
multiValueHeaders               :: HashMap (CI Text) [Text]
    , ProxyRequest a -> HashMap Text Text
pathParameters                  :: HashMap Text Text
    , ProxyRequest a -> HashMap Text Text
stageVariables                  :: HashMap Text Text
    , ProxyRequest a -> RequestContext a
requestContext                  :: RequestContext a
    , ProxyRequest a -> Text
resource                        :: Text
    , ProxyRequest a -> Text
httpMethod                      :: Text
    , ProxyRequest a -> HashMap Text Text
queryStringParameters           :: HashMap Text Text
    , ProxyRequest a -> HashMap Text [Text]
multiValueQueryStringParameters :: HashMap Text [Text]
    , ProxyRequest a -> ByteString
body                            :: ByteString
    } deriving (ProxyRequest a -> ProxyRequest a -> Bool
(ProxyRequest a -> ProxyRequest a -> Bool)
-> (ProxyRequest a -> ProxyRequest a -> Bool)
-> Eq (ProxyRequest a)
forall a. Eq a => ProxyRequest a -> ProxyRequest a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProxyRequest a -> ProxyRequest a -> Bool
$c/= :: forall a. Eq a => ProxyRequest a -> ProxyRequest a -> Bool
== :: ProxyRequest a -> ProxyRequest a -> Bool
$c== :: forall a. Eq a => ProxyRequest a -> ProxyRequest a -> Bool
Eq, (forall x. ProxyRequest a -> Rep (ProxyRequest a) x)
-> (forall x. Rep (ProxyRequest a) x -> ProxyRequest a)
-> Generic (ProxyRequest a)
forall x. Rep (ProxyRequest a) x -> ProxyRequest a
forall x. ProxyRequest a -> Rep (ProxyRequest a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ProxyRequest a) x -> ProxyRequest a
forall a x. ProxyRequest a -> Rep (ProxyRequest a) x
$cto :: forall a x. Rep (ProxyRequest a) x -> ProxyRequest a
$cfrom :: forall a x. ProxyRequest a -> Rep (ProxyRequest a) x
Generic, Int -> ProxyRequest a -> ShowS
[ProxyRequest a] -> ShowS
ProxyRequest a -> String
(Int -> ProxyRequest a -> ShowS)
-> (ProxyRequest a -> String)
-> ([ProxyRequest a] -> ShowS)
-> Show (ProxyRequest a)
forall a. Show a => Int -> ProxyRequest a -> ShowS
forall a. Show a => [ProxyRequest a] -> ShowS
forall a. Show a => ProxyRequest a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProxyRequest a] -> ShowS
$cshowList :: forall a. Show a => [ProxyRequest a] -> ShowS
show :: ProxyRequest a -> String
$cshow :: forall a. Show a => ProxyRequest a -> String
showsPrec :: Int -> ProxyRequest a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ProxyRequest a -> ShowS
Show)

toCIHashMap :: (Eq k, FoldCase k, Hashable k) => HashMap k a -> HashMap (CI k) a
toCIHashMap :: HashMap k a -> HashMap (CI k) a
toCIHashMap = (k -> a -> HashMap (CI k) a -> HashMap (CI k) a)
-> HashMap (CI k) a -> HashMap k a -> HashMap (CI k) a
forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
foldrWithKey (CI k -> a -> HashMap (CI k) a -> HashMap (CI k) a
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
insert (CI k -> a -> HashMap (CI k) a -> HashMap (CI k) a)
-> (k -> CI k) -> k -> a -> HashMap (CI k) a -> HashMap (CI k) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. k -> CI k
forall s. FoldCase s => s -> CI s
mk) HashMap (CI k) a
forall a. Monoid a => a
mempty

fromCIHashMap :: (Eq k, Hashable k) => HashMap (CI k) a -> HashMap k a
fromCIHashMap :: HashMap (CI k) a -> HashMap k a
fromCIHashMap = (CI k -> a -> HashMap k a -> HashMap k a)
-> HashMap k a -> HashMap (CI k) a -> HashMap k a
forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
foldrWithKey (k -> a -> HashMap k a -> HashMap k a
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
insert (k -> a -> HashMap k a -> HashMap k a)
-> (CI k -> k) -> CI k -> a -> HashMap k a -> HashMap k a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CI k -> k
forall s. CI s -> s
original) HashMap k a
forall a. Monoid a => a
mempty

toByteString :: Bool -> TL.Text -> ByteString
toByteString :: Bool -> Text -> ByteString
toByteString Bool
isBase64Encoded =
    if Bool
isBase64Encoded
        then ByteString -> ByteString
decodeLenient (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TLE.encodeUtf8
        else Text -> ByteString
TLE.encodeUtf8

toMaybe :: Bool -> a -> Maybe a
toMaybe :: Bool -> a -> Maybe a
toMaybe Bool
b a
a = if Bool
b then a -> Maybe a
forall a. a -> Maybe a
Just a
a else Maybe a
forall a. Maybe a
Nothing

-- | For ignoring API Gateway custom authorizer values
type NoAuthorizer = Value

-- | For ensuring that there were no API Gateway custom authorizer values (this
-- is not likely to be useful, you probably want 'NoAuthorizer')
type StrictlyNoAuthorizer = Void

instance FromJSON a => FromJSON (ProxyRequest a) where
    parseJSON :: Value -> Parser (ProxyRequest a)
parseJSON = String
-> (Object -> Parser (ProxyRequest a))
-> Value
-> Parser (ProxyRequest a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ProxyRequest" ((Object -> Parser (ProxyRequest a))
 -> Value -> Parser (ProxyRequest a))
-> (Object -> Parser (ProxyRequest a))
-> Value
-> Parser (ProxyRequest a)
forall a b. (a -> b) -> a -> b
$ \Object
v ->
        Text
-> HashMap (CI Text) Text
-> HashMap (CI Text) [Text]
-> HashMap Text Text
-> HashMap Text Text
-> RequestContext a
-> Text
-> Text
-> HashMap Text Text
-> HashMap Text [Text]
-> ByteString
-> ProxyRequest a
forall a.
Text
-> HashMap (CI Text) Text
-> HashMap (CI Text) [Text]
-> HashMap Text Text
-> HashMap Text Text
-> RequestContext a
-> Text
-> Text
-> HashMap Text Text
-> HashMap Text [Text]
-> ByteString
-> ProxyRequest a
ProxyRequest (Text
 -> HashMap (CI Text) Text
 -> HashMap (CI Text) [Text]
 -> HashMap Text Text
 -> HashMap Text Text
 -> RequestContext a
 -> Text
 -> Text
 -> HashMap Text Text
 -> HashMap Text [Text]
 -> ByteString
 -> ProxyRequest a)
-> Parser Text
-> Parser
     (HashMap (CI Text) Text
      -> HashMap (CI Text) [Text]
      -> HashMap Text Text
      -> HashMap Text Text
      -> RequestContext a
      -> Text
      -> Text
      -> HashMap Text Text
      -> HashMap Text [Text]
      -> ByteString
      -> ProxyRequest a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"path" Parser
  (HashMap (CI Text) Text
   -> HashMap (CI Text) [Text]
   -> HashMap Text Text
   -> HashMap Text Text
   -> RequestContext a
   -> Text
   -> Text
   -> HashMap Text Text
   -> HashMap Text [Text]
   -> ByteString
   -> ProxyRequest a)
-> Parser (HashMap (CI Text) Text)
-> Parser
     (HashMap (CI Text) [Text]
      -> HashMap Text Text
      -> HashMap Text Text
      -> RequestContext a
      -> Text
      -> Text
      -> HashMap Text Text
      -> HashMap Text [Text]
      -> ByteString
      -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        (Object
v Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"headers" Parser (Maybe (HashMap Text Text))
-> (Maybe (HashMap Text Text) -> HashMap (CI Text) Text)
-> Parser (HashMap (CI Text) Text)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> HashMap Text Text -> HashMap (CI Text) Text
forall k a.
(Eq k, FoldCase k, Hashable k) =>
HashMap k a -> HashMap (CI k) a
toCIHashMap (HashMap Text Text -> HashMap (CI Text) Text)
-> (Maybe (HashMap Text Text) -> HashMap Text Text)
-> Maybe (HashMap Text Text)
-> HashMap (CI Text) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (HashMap Text Text) -> HashMap Text Text
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold) Parser
  (HashMap (CI Text) [Text]
   -> HashMap Text Text
   -> HashMap Text Text
   -> RequestContext a
   -> Text
   -> Text
   -> HashMap Text Text
   -> HashMap Text [Text]
   -> ByteString
   -> ProxyRequest a)
-> Parser (HashMap (CI Text) [Text])
-> Parser
     (HashMap Text Text
      -> HashMap Text Text
      -> RequestContext a
      -> Text
      -> Text
      -> HashMap Text Text
      -> HashMap Text [Text]
      -> ByteString
      -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        (Object
v Object -> Text -> Parser (Maybe (HashMap Text [Text]))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"multiValueHeaders" Parser (Maybe (HashMap Text [Text]))
-> (Maybe (HashMap Text [Text]) -> HashMap (CI Text) [Text])
-> Parser (HashMap (CI Text) [Text])
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> HashMap Text [Text] -> HashMap (CI Text) [Text]
forall k a.
(Eq k, FoldCase k, Hashable k) =>
HashMap k a -> HashMap (CI k) a
toCIHashMap (HashMap Text [Text] -> HashMap (CI Text) [Text])
-> (Maybe (HashMap Text [Text]) -> HashMap Text [Text])
-> Maybe (HashMap Text [Text])
-> HashMap (CI Text) [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (HashMap Text [Text]) -> HashMap Text [Text]
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold) Parser
  (HashMap Text Text
   -> HashMap Text Text
   -> RequestContext a
   -> Text
   -> Text
   -> HashMap Text Text
   -> HashMap Text [Text]
   -> ByteString
   -> ProxyRequest a)
-> Parser (HashMap Text Text)
-> Parser
     (HashMap Text Text
      -> RequestContext a
      -> Text
      -> Text
      -> HashMap Text Text
      -> HashMap Text [Text]
      -> ByteString
      -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        (Object
v Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"pathParameters" Parser (Maybe (HashMap Text Text))
-> (Maybe (HashMap Text Text) -> HashMap Text Text)
-> Parser (HashMap Text Text)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Maybe (HashMap Text Text) -> HashMap Text Text
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold) Parser
  (HashMap Text Text
   -> RequestContext a
   -> Text
   -> Text
   -> HashMap Text Text
   -> HashMap Text [Text]
   -> ByteString
   -> ProxyRequest a)
-> Parser (HashMap Text Text)
-> Parser
     (RequestContext a
      -> Text
      -> Text
      -> HashMap Text Text
      -> HashMap Text [Text]
      -> ByteString
      -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        (Object
v Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"stageVariables" Parser (Maybe (HashMap Text Text))
-> (Maybe (HashMap Text Text) -> HashMap Text Text)
-> Parser (HashMap Text Text)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Maybe (HashMap Text Text) -> HashMap Text Text
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold) Parser
  (RequestContext a
   -> Text
   -> Text
   -> HashMap Text Text
   -> HashMap Text [Text]
   -> ByteString
   -> ProxyRequest a)
-> Parser (RequestContext a)
-> Parser
     (Text
      -> Text
      -> HashMap Text Text
      -> HashMap Text [Text]
      -> ByteString
      -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser (RequestContext a)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"requestContext" Parser
  (Text
   -> Text
   -> HashMap Text Text
   -> HashMap Text [Text]
   -> ByteString
   -> ProxyRequest a)
-> Parser Text
-> Parser
     (Text
      -> HashMap Text Text
      -> HashMap Text [Text]
      -> ByteString
      -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"resource" Parser
  (Text
   -> HashMap Text Text
   -> HashMap Text [Text]
   -> ByteString
   -> ProxyRequest a)
-> Parser Text
-> Parser
     (HashMap Text Text
      -> HashMap Text [Text] -> ByteString -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"httpMethod" Parser
  (HashMap Text Text
   -> HashMap Text [Text] -> ByteString -> ProxyRequest a)
-> Parser (HashMap Text Text)
-> Parser (HashMap Text [Text] -> ByteString -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        (Object
v Object -> Text -> Parser (Maybe (HashMap Text Text))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"queryStringParameters" Parser (Maybe (HashMap Text Text))
-> (Maybe (HashMap Text Text) -> HashMap Text Text)
-> Parser (HashMap Text Text)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Maybe (HashMap Text Text) -> HashMap Text Text
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold) Parser (HashMap Text [Text] -> ByteString -> ProxyRequest a)
-> Parser (HashMap Text [Text])
-> Parser (ByteString -> ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        (Object
v Object -> Text -> Parser (Maybe (HashMap Text [Text]))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"multiValueQueryStringParameters" Parser (Maybe (HashMap Text [Text]))
-> (Maybe (HashMap Text [Text]) -> HashMap Text [Text])
-> Parser (HashMap Text [Text])
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Maybe (HashMap Text [Text]) -> HashMap Text [Text]
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold) Parser (ByteString -> ProxyRequest a)
-> Parser ByteString -> Parser (ProxyRequest a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
        (Bool -> Text -> ByteString
toByteString (Bool -> Text -> ByteString)
-> Parser Bool -> Parser (Text -> ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"isBase64Encoded" Parser (Text -> ByteString) -> Parser Text -> Parser ByteString
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"body" Parser (Maybe Text) -> (Maybe Text -> Text) -> Parser Text
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Maybe Text -> Text
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold))

-- | @since 0.4.8
instance ToJSON a => ToJSON (ProxyRequest a) where
    toJSON :: ProxyRequest a -> Value
toJSON ProxyRequest a
r = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes
        [ Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"path" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ProxyRequest a -> Text
forall a. ProxyRequest a -> Text
path (ProxyRequest a
r :: ProxyRequest a)
        , Bool -> Pair -> Maybe Pair
forall a. Bool -> a -> Maybe a
toMaybe (Bool -> Bool
not (Bool -> Bool)
-> (HashMap (CI Text) Text -> Bool)
-> HashMap (CI Text) Text
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap (CI Text) Text -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (HashMap (CI Text) Text -> Bool) -> HashMap (CI Text) Text -> Bool
forall a b. (a -> b) -> a -> b
$ ProxyRequest a -> HashMap (CI Text) Text
forall a. ProxyRequest a -> HashMap (CI Text) Text
headers ProxyRequest a
r) (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$
              Text
"headers" Text -> HashMap Text Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= HashMap (CI Text) Text -> HashMap Text Text
forall k a. (Eq k, Hashable k) => HashMap (CI k) a -> HashMap k a
fromCIHashMap (ProxyRequest a -> HashMap (CI Text) Text
forall a. ProxyRequest a -> HashMap (CI Text) Text
headers ProxyRequest a
r)
        , Bool -> Pair -> Maybe Pair
forall a. Bool -> a -> Maybe a
toMaybe (Bool -> Bool
not (Bool -> Bool)
-> (HashMap (CI Text) [Text] -> Bool)
-> HashMap (CI Text) [Text]
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap (CI Text) [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (HashMap (CI Text) [Text] -> Bool)
-> HashMap (CI Text) [Text] -> Bool
forall a b. (a -> b) -> a -> b
$ ProxyRequest a -> HashMap (CI Text) [Text]
forall a. ProxyRequest a -> HashMap (CI Text) [Text]
multiValueHeaders ProxyRequest a
r) (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$
              Text
"multiValueHeaders" Text -> HashMap Text [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= HashMap (CI Text) [Text] -> HashMap Text [Text]
forall k a. (Eq k, Hashable k) => HashMap (CI k) a -> HashMap k a
fromCIHashMap (ProxyRequest a -> HashMap (CI Text) [Text]
forall a. ProxyRequest a -> HashMap (CI Text) [Text]
multiValueHeaders ProxyRequest a
r)
        , Bool -> Pair -> Maybe Pair
forall a. Bool -> a -> Maybe a
toMaybe (Bool -> Bool
not (Bool -> Bool)
-> (HashMap Text Text -> Bool) -> HashMap Text Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Text Text -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (HashMap Text Text -> Bool) -> HashMap Text Text -> Bool
forall a b. (a -> b) -> a -> b
$ ProxyRequest a -> HashMap Text Text
forall a. ProxyRequest a -> HashMap Text Text
pathParameters ProxyRequest a
r) (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$
              Text
"pathParameters" Text -> HashMap Text Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ProxyRequest a -> HashMap Text Text
forall a. ProxyRequest a -> HashMap Text Text
pathParameters ProxyRequest a
r
        , Bool -> Pair -> Maybe Pair
forall a. Bool -> a -> Maybe a
toMaybe (Bool -> Bool
not (Bool -> Bool)
-> (HashMap Text Text -> Bool) -> HashMap Text Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Text Text -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (HashMap Text Text -> Bool) -> HashMap Text Text -> Bool
forall a b. (a -> b) -> a -> b
$ ProxyRequest a -> HashMap Text Text
forall a. ProxyRequest a -> HashMap Text Text
stageVariables ProxyRequest a
r) (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$
              Text
"stageVariables" Text -> HashMap Text Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ProxyRequest a -> HashMap Text Text
forall a. ProxyRequest a -> HashMap Text Text
stageVariables ProxyRequest a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"requestContext" Text -> RequestContext a -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ProxyRequest a -> RequestContext a
forall a. ProxyRequest a -> RequestContext a
requestContext ProxyRequest a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"resource" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ProxyRequest a -> Text
forall a. ProxyRequest a -> Text
resource ProxyRequest a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"httpMethod" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ProxyRequest a -> Text
forall a. ProxyRequest a -> Text
httpMethod (ProxyRequest a
r :: ProxyRequest a)
        , Bool -> Pair -> Maybe Pair
forall a. Bool -> a -> Maybe a
toMaybe (Bool -> Bool
not (Bool -> Bool)
-> (HashMap Text Text -> Bool) -> HashMap Text Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Text Text -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (HashMap Text Text -> Bool) -> HashMap Text Text -> Bool
forall a b. (a -> b) -> a -> b
$ ProxyRequest a -> HashMap Text Text
forall a. ProxyRequest a -> HashMap Text Text
queryStringParameters ProxyRequest a
r) (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$
              Text
"queryStringParameters" Text -> HashMap Text Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ProxyRequest a -> HashMap Text Text
forall a. ProxyRequest a -> HashMap Text Text
queryStringParameters ProxyRequest a
r
        , Bool -> Pair -> Maybe Pair
forall a. Bool -> a -> Maybe a
toMaybe (Bool -> Bool
not (Bool -> Bool)
-> (HashMap Text [Text] -> Bool) -> HashMap Text [Text] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Text [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (HashMap Text [Text] -> Bool) -> HashMap Text [Text] -> Bool
forall a b. (a -> b) -> a -> b
$ ProxyRequest a -> HashMap Text [Text]
forall a. ProxyRequest a -> HashMap Text [Text]
multiValueQueryStringParameters ProxyRequest a
r) (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$
              Text
"multiValueQueryStringParameters" Text -> HashMap Text [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=
                  ProxyRequest a -> HashMap Text [Text]
forall a. ProxyRequest a -> HashMap Text [Text]
multiValueQueryStringParameters ProxyRequest a
r
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"isBase64Encoded" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
True
        , Pair -> Maybe Pair
forall a. a -> Maybe a
Just (Pair -> Maybe Pair) -> Pair -> Maybe Pair
forall a b. (a -> b) -> a -> b
$ Text
"body" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ByteString -> Text
TLE.decodeUtf8 (ByteString -> ByteString
encode (ProxyRequest a -> ByteString
forall a. ProxyRequest a -> ByteString
body ProxyRequest a
r))
        ]