{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.AppMesh.Types.HttpGatewayRouteMatch
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AppMesh.Types.HttpGatewayRouteMatch where

import Amazonka.AppMesh.Types.GatewayRouteHostnameMatch
import Amazonka.AppMesh.Types.HttpGatewayRouteHeader
import Amazonka.AppMesh.Types.HttpMethod
import Amazonka.AppMesh.Types.HttpPathMatch
import Amazonka.AppMesh.Types.HttpQueryParameter
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | An object that represents the criteria for determining a request match.
--
-- /See:/ 'newHttpGatewayRouteMatch' smart constructor.
data HttpGatewayRouteMatch = HttpGatewayRouteMatch'
  { -- | The client request headers to match on.
    HttpGatewayRouteMatch -> Maybe (NonEmpty HttpGatewayRouteHeader)
headers :: Prelude.Maybe (Prelude.NonEmpty HttpGatewayRouteHeader),
    -- | The host name to match on.
    HttpGatewayRouteMatch -> Maybe GatewayRouteHostnameMatch
hostname :: Prelude.Maybe GatewayRouteHostnameMatch,
    -- | The method to match on.
    HttpGatewayRouteMatch -> Maybe HttpMethod
method :: Prelude.Maybe HttpMethod,
    -- | The path to match on.
    HttpGatewayRouteMatch -> Maybe HttpPathMatch
path :: Prelude.Maybe HttpPathMatch,
    -- | The port number to match on.
    HttpGatewayRouteMatch -> Maybe Natural
port :: Prelude.Maybe Prelude.Natural,
    -- | Specifies the path to match requests with. This parameter must always
    -- start with @\/@, which by itself matches all requests to the virtual
    -- service name. You can also match for path-based routing of requests. For
    -- example, if your virtual service name is @my-service.local@ and you want
    -- the route to match requests to @my-service.local\/metrics@, your prefix
    -- should be @\/metrics@.
    HttpGatewayRouteMatch -> Maybe Text
prefix :: Prelude.Maybe Prelude.Text,
    -- | The query parameter to match on.
    HttpGatewayRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
queryParameters :: Prelude.Maybe (Prelude.NonEmpty HttpQueryParameter)
  }
  deriving (HttpGatewayRouteMatch -> HttpGatewayRouteMatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HttpGatewayRouteMatch -> HttpGatewayRouteMatch -> Bool
$c/= :: HttpGatewayRouteMatch -> HttpGatewayRouteMatch -> Bool
== :: HttpGatewayRouteMatch -> HttpGatewayRouteMatch -> Bool
$c== :: HttpGatewayRouteMatch -> HttpGatewayRouteMatch -> Bool
Prelude.Eq, ReadPrec [HttpGatewayRouteMatch]
ReadPrec HttpGatewayRouteMatch
Int -> ReadS HttpGatewayRouteMatch
ReadS [HttpGatewayRouteMatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HttpGatewayRouteMatch]
$creadListPrec :: ReadPrec [HttpGatewayRouteMatch]
readPrec :: ReadPrec HttpGatewayRouteMatch
$creadPrec :: ReadPrec HttpGatewayRouteMatch
readList :: ReadS [HttpGatewayRouteMatch]
$creadList :: ReadS [HttpGatewayRouteMatch]
readsPrec :: Int -> ReadS HttpGatewayRouteMatch
$creadsPrec :: Int -> ReadS HttpGatewayRouteMatch
Prelude.Read, Int -> HttpGatewayRouteMatch -> ShowS
[HttpGatewayRouteMatch] -> ShowS
HttpGatewayRouteMatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HttpGatewayRouteMatch] -> ShowS
$cshowList :: [HttpGatewayRouteMatch] -> ShowS
show :: HttpGatewayRouteMatch -> String
$cshow :: HttpGatewayRouteMatch -> String
showsPrec :: Int -> HttpGatewayRouteMatch -> ShowS
$cshowsPrec :: Int -> HttpGatewayRouteMatch -> ShowS
Prelude.Show, forall x. Rep HttpGatewayRouteMatch x -> HttpGatewayRouteMatch
forall x. HttpGatewayRouteMatch -> Rep HttpGatewayRouteMatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HttpGatewayRouteMatch x -> HttpGatewayRouteMatch
$cfrom :: forall x. HttpGatewayRouteMatch -> Rep HttpGatewayRouteMatch x
Prelude.Generic)

-- |
-- Create a value of 'HttpGatewayRouteMatch' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'headers', 'httpGatewayRouteMatch_headers' - The client request headers to match on.
--
-- 'hostname', 'httpGatewayRouteMatch_hostname' - The host name to match on.
--
-- 'method', 'httpGatewayRouteMatch_method' - The method to match on.
--
-- 'path', 'httpGatewayRouteMatch_path' - The path to match on.
--
-- 'port', 'httpGatewayRouteMatch_port' - The port number to match on.
--
-- 'prefix', 'httpGatewayRouteMatch_prefix' - Specifies the path to match requests with. This parameter must always
-- start with @\/@, which by itself matches all requests to the virtual
-- service name. You can also match for path-based routing of requests. For
-- example, if your virtual service name is @my-service.local@ and you want
-- the route to match requests to @my-service.local\/metrics@, your prefix
-- should be @\/metrics@.
--
-- 'queryParameters', 'httpGatewayRouteMatch_queryParameters' - The query parameter to match on.
newHttpGatewayRouteMatch ::
  HttpGatewayRouteMatch
newHttpGatewayRouteMatch :: HttpGatewayRouteMatch
newHttpGatewayRouteMatch =
  HttpGatewayRouteMatch'
    { $sel:headers:HttpGatewayRouteMatch' :: Maybe (NonEmpty HttpGatewayRouteHeader)
headers = forall a. Maybe a
Prelude.Nothing,
      $sel:hostname:HttpGatewayRouteMatch' :: Maybe GatewayRouteHostnameMatch
hostname = forall a. Maybe a
Prelude.Nothing,
      $sel:method:HttpGatewayRouteMatch' :: Maybe HttpMethod
method = forall a. Maybe a
Prelude.Nothing,
      $sel:path:HttpGatewayRouteMatch' :: Maybe HttpPathMatch
path = forall a. Maybe a
Prelude.Nothing,
      $sel:port:HttpGatewayRouteMatch' :: Maybe Natural
port = forall a. Maybe a
Prelude.Nothing,
      $sel:prefix:HttpGatewayRouteMatch' :: Maybe Text
prefix = forall a. Maybe a
Prelude.Nothing,
      $sel:queryParameters:HttpGatewayRouteMatch' :: Maybe (NonEmpty HttpQueryParameter)
queryParameters = forall a. Maybe a
Prelude.Nothing
    }

-- | The client request headers to match on.
httpGatewayRouteMatch_headers :: Lens.Lens' HttpGatewayRouteMatch (Prelude.Maybe (Prelude.NonEmpty HttpGatewayRouteHeader))
httpGatewayRouteMatch_headers :: Lens'
  HttpGatewayRouteMatch (Maybe (NonEmpty HttpGatewayRouteHeader))
httpGatewayRouteMatch_headers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpGatewayRouteMatch' {Maybe (NonEmpty HttpGatewayRouteHeader)
headers :: Maybe (NonEmpty HttpGatewayRouteHeader)
$sel:headers:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpGatewayRouteHeader)
headers} -> Maybe (NonEmpty HttpGatewayRouteHeader)
headers) (\s :: HttpGatewayRouteMatch
s@HttpGatewayRouteMatch' {} Maybe (NonEmpty HttpGatewayRouteHeader)
a -> HttpGatewayRouteMatch
s {$sel:headers:HttpGatewayRouteMatch' :: Maybe (NonEmpty HttpGatewayRouteHeader)
headers = Maybe (NonEmpty HttpGatewayRouteHeader)
a} :: HttpGatewayRouteMatch) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. 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)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The host name to match on.
httpGatewayRouteMatch_hostname :: Lens.Lens' HttpGatewayRouteMatch (Prelude.Maybe GatewayRouteHostnameMatch)
httpGatewayRouteMatch_hostname :: Lens' HttpGatewayRouteMatch (Maybe GatewayRouteHostnameMatch)
httpGatewayRouteMatch_hostname = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpGatewayRouteMatch' {Maybe GatewayRouteHostnameMatch
hostname :: Maybe GatewayRouteHostnameMatch
$sel:hostname:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe GatewayRouteHostnameMatch
hostname} -> Maybe GatewayRouteHostnameMatch
hostname) (\s :: HttpGatewayRouteMatch
s@HttpGatewayRouteMatch' {} Maybe GatewayRouteHostnameMatch
a -> HttpGatewayRouteMatch
s {$sel:hostname:HttpGatewayRouteMatch' :: Maybe GatewayRouteHostnameMatch
hostname = Maybe GatewayRouteHostnameMatch
a} :: HttpGatewayRouteMatch)

-- | The method to match on.
httpGatewayRouteMatch_method :: Lens.Lens' HttpGatewayRouteMatch (Prelude.Maybe HttpMethod)
httpGatewayRouteMatch_method :: Lens' HttpGatewayRouteMatch (Maybe HttpMethod)
httpGatewayRouteMatch_method = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpGatewayRouteMatch' {Maybe HttpMethod
method :: Maybe HttpMethod
$sel:method:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpMethod
method} -> Maybe HttpMethod
method) (\s :: HttpGatewayRouteMatch
s@HttpGatewayRouteMatch' {} Maybe HttpMethod
a -> HttpGatewayRouteMatch
s {$sel:method:HttpGatewayRouteMatch' :: Maybe HttpMethod
method = Maybe HttpMethod
a} :: HttpGatewayRouteMatch)

-- | The path to match on.
httpGatewayRouteMatch_path :: Lens.Lens' HttpGatewayRouteMatch (Prelude.Maybe HttpPathMatch)
httpGatewayRouteMatch_path :: Lens' HttpGatewayRouteMatch (Maybe HttpPathMatch)
httpGatewayRouteMatch_path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpGatewayRouteMatch' {Maybe HttpPathMatch
path :: Maybe HttpPathMatch
$sel:path:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpPathMatch
path} -> Maybe HttpPathMatch
path) (\s :: HttpGatewayRouteMatch
s@HttpGatewayRouteMatch' {} Maybe HttpPathMatch
a -> HttpGatewayRouteMatch
s {$sel:path:HttpGatewayRouteMatch' :: Maybe HttpPathMatch
path = Maybe HttpPathMatch
a} :: HttpGatewayRouteMatch)

-- | The port number to match on.
httpGatewayRouteMatch_port :: Lens.Lens' HttpGatewayRouteMatch (Prelude.Maybe Prelude.Natural)
httpGatewayRouteMatch_port :: Lens' HttpGatewayRouteMatch (Maybe Natural)
httpGatewayRouteMatch_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpGatewayRouteMatch' {Maybe Natural
port :: Maybe Natural
$sel:port:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Natural
port} -> Maybe Natural
port) (\s :: HttpGatewayRouteMatch
s@HttpGatewayRouteMatch' {} Maybe Natural
a -> HttpGatewayRouteMatch
s {$sel:port:HttpGatewayRouteMatch' :: Maybe Natural
port = Maybe Natural
a} :: HttpGatewayRouteMatch)

-- | Specifies the path to match requests with. This parameter must always
-- start with @\/@, which by itself matches all requests to the virtual
-- service name. You can also match for path-based routing of requests. For
-- example, if your virtual service name is @my-service.local@ and you want
-- the route to match requests to @my-service.local\/metrics@, your prefix
-- should be @\/metrics@.
httpGatewayRouteMatch_prefix :: Lens.Lens' HttpGatewayRouteMatch (Prelude.Maybe Prelude.Text)
httpGatewayRouteMatch_prefix :: Lens' HttpGatewayRouteMatch (Maybe Text)
httpGatewayRouteMatch_prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpGatewayRouteMatch' {Maybe Text
prefix :: Maybe Text
$sel:prefix:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Text
prefix} -> Maybe Text
prefix) (\s :: HttpGatewayRouteMatch
s@HttpGatewayRouteMatch' {} Maybe Text
a -> HttpGatewayRouteMatch
s {$sel:prefix:HttpGatewayRouteMatch' :: Maybe Text
prefix = Maybe Text
a} :: HttpGatewayRouteMatch)

-- | The query parameter to match on.
httpGatewayRouteMatch_queryParameters :: Lens.Lens' HttpGatewayRouteMatch (Prelude.Maybe (Prelude.NonEmpty HttpQueryParameter))
httpGatewayRouteMatch_queryParameters :: Lens' HttpGatewayRouteMatch (Maybe (NonEmpty HttpQueryParameter))
httpGatewayRouteMatch_queryParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpGatewayRouteMatch' {Maybe (NonEmpty HttpQueryParameter)
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
$sel:queryParameters:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
queryParameters} -> Maybe (NonEmpty HttpQueryParameter)
queryParameters) (\s :: HttpGatewayRouteMatch
s@HttpGatewayRouteMatch' {} Maybe (NonEmpty HttpQueryParameter)
a -> HttpGatewayRouteMatch
s {$sel:queryParameters:HttpGatewayRouteMatch' :: Maybe (NonEmpty HttpQueryParameter)
queryParameters = Maybe (NonEmpty HttpQueryParameter)
a} :: HttpGatewayRouteMatch) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. 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)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Data.FromJSON HttpGatewayRouteMatch where
  parseJSON :: Value -> Parser HttpGatewayRouteMatch
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HttpGatewayRouteMatch"
      ( \Object
x ->
          Maybe (NonEmpty HttpGatewayRouteHeader)
-> Maybe GatewayRouteHostnameMatch
-> Maybe HttpMethod
-> Maybe HttpPathMatch
-> Maybe Natural
-> Maybe Text
-> Maybe (NonEmpty HttpQueryParameter)
-> HttpGatewayRouteMatch
HttpGatewayRouteMatch'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"headers")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"hostname")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"method")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"path")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"port")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"prefix")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"queryParameters")
      )

instance Prelude.Hashable HttpGatewayRouteMatch where
  hashWithSalt :: Int -> HttpGatewayRouteMatch -> Int
hashWithSalt Int
_salt HttpGatewayRouteMatch' {Maybe Natural
Maybe (NonEmpty HttpGatewayRouteHeader)
Maybe (NonEmpty HttpQueryParameter)
Maybe Text
Maybe GatewayRouteHostnameMatch
Maybe HttpMethod
Maybe HttpPathMatch
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
prefix :: Maybe Text
port :: Maybe Natural
path :: Maybe HttpPathMatch
method :: Maybe HttpMethod
hostname :: Maybe GatewayRouteHostnameMatch
headers :: Maybe (NonEmpty HttpGatewayRouteHeader)
$sel:queryParameters:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
$sel:prefix:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Text
$sel:port:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Natural
$sel:path:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpPathMatch
$sel:method:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpMethod
$sel:hostname:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe GatewayRouteHostnameMatch
$sel:headers:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpGatewayRouteHeader)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty HttpGatewayRouteHeader)
headers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GatewayRouteHostnameMatch
hostname
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpMethod
method
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpPathMatch
path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
port
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
prefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty HttpQueryParameter)
queryParameters

instance Prelude.NFData HttpGatewayRouteMatch where
  rnf :: HttpGatewayRouteMatch -> ()
rnf HttpGatewayRouteMatch' {Maybe Natural
Maybe (NonEmpty HttpGatewayRouteHeader)
Maybe (NonEmpty HttpQueryParameter)
Maybe Text
Maybe GatewayRouteHostnameMatch
Maybe HttpMethod
Maybe HttpPathMatch
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
prefix :: Maybe Text
port :: Maybe Natural
path :: Maybe HttpPathMatch
method :: Maybe HttpMethod
hostname :: Maybe GatewayRouteHostnameMatch
headers :: Maybe (NonEmpty HttpGatewayRouteHeader)
$sel:queryParameters:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
$sel:prefix:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Text
$sel:port:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Natural
$sel:path:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpPathMatch
$sel:method:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpMethod
$sel:hostname:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe GatewayRouteHostnameMatch
$sel:headers:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpGatewayRouteHeader)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty HttpGatewayRouteHeader)
headers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GatewayRouteHostnameMatch
hostname
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpMethod
method
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpPathMatch
path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
port
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
prefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty HttpQueryParameter)
queryParameters

instance Data.ToJSON HttpGatewayRouteMatch where
  toJSON :: HttpGatewayRouteMatch -> Value
toJSON HttpGatewayRouteMatch' {Maybe Natural
Maybe (NonEmpty HttpGatewayRouteHeader)
Maybe (NonEmpty HttpQueryParameter)
Maybe Text
Maybe GatewayRouteHostnameMatch
Maybe HttpMethod
Maybe HttpPathMatch
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
prefix :: Maybe Text
port :: Maybe Natural
path :: Maybe HttpPathMatch
method :: Maybe HttpMethod
hostname :: Maybe GatewayRouteHostnameMatch
headers :: Maybe (NonEmpty HttpGatewayRouteHeader)
$sel:queryParameters:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
$sel:prefix:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Text
$sel:port:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe Natural
$sel:path:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpPathMatch
$sel:method:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe HttpMethod
$sel:hostname:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe GatewayRouteHostnameMatch
$sel:headers:HttpGatewayRouteMatch' :: HttpGatewayRouteMatch -> Maybe (NonEmpty HttpGatewayRouteHeader)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"headers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty HttpGatewayRouteHeader)
headers,
            (Key
"hostname" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GatewayRouteHostnameMatch
hostname,
            (Key
"method" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HttpMethod
method,
            (Key
"path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HttpPathMatch
path,
            (Key
"port" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
port,
            (Key
"prefix" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
prefix,
            (Key
"queryParameters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty HttpQueryParameter)
queryParameters
          ]
      )