{-# 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.HttpRouteMatch
-- 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.HttpRouteMatch where

import Amazonka.AppMesh.Types.HttpMethod
import Amazonka.AppMesh.Types.HttpPathMatch
import Amazonka.AppMesh.Types.HttpQueryParameter
import Amazonka.AppMesh.Types.HttpRouteHeader
import Amazonka.AppMesh.Types.HttpScheme
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 requirements for a route to match HTTP
-- requests for a virtual router.
--
-- /See:/ 'newHttpRouteMatch' smart constructor.
data HttpRouteMatch = HttpRouteMatch'
  { -- | The client request headers to match on.
    HttpRouteMatch -> Maybe (NonEmpty HttpRouteHeader)
headers :: Prelude.Maybe (Prelude.NonEmpty HttpRouteHeader),
    -- | The client request method to match on. Specify only one.
    HttpRouteMatch -> Maybe HttpMethod
method :: Prelude.Maybe HttpMethod,
    -- | The client request path to match on.
    HttpRouteMatch -> Maybe HttpPathMatch
path :: Prelude.Maybe HttpPathMatch,
    -- | The port number to match on.
    HttpRouteMatch -> 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@.
    HttpRouteMatch -> Maybe Text
prefix :: Prelude.Maybe Prelude.Text,
    -- | The client request query parameters to match on.
    HttpRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
queryParameters :: Prelude.Maybe (Prelude.NonEmpty HttpQueryParameter),
    -- | The client request scheme to match on. Specify only one. Applicable only
    -- for HTTP2 routes.
    HttpRouteMatch -> Maybe HttpScheme
scheme :: Prelude.Maybe HttpScheme
  }
  deriving (HttpRouteMatch -> HttpRouteMatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HttpRouteMatch -> HttpRouteMatch -> Bool
$c/= :: HttpRouteMatch -> HttpRouteMatch -> Bool
== :: HttpRouteMatch -> HttpRouteMatch -> Bool
$c== :: HttpRouteMatch -> HttpRouteMatch -> Bool
Prelude.Eq, ReadPrec [HttpRouteMatch]
ReadPrec HttpRouteMatch
Int -> ReadS HttpRouteMatch
ReadS [HttpRouteMatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HttpRouteMatch]
$creadListPrec :: ReadPrec [HttpRouteMatch]
readPrec :: ReadPrec HttpRouteMatch
$creadPrec :: ReadPrec HttpRouteMatch
readList :: ReadS [HttpRouteMatch]
$creadList :: ReadS [HttpRouteMatch]
readsPrec :: Int -> ReadS HttpRouteMatch
$creadsPrec :: Int -> ReadS HttpRouteMatch
Prelude.Read, Int -> HttpRouteMatch -> ShowS
[HttpRouteMatch] -> ShowS
HttpRouteMatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HttpRouteMatch] -> ShowS
$cshowList :: [HttpRouteMatch] -> ShowS
show :: HttpRouteMatch -> String
$cshow :: HttpRouteMatch -> String
showsPrec :: Int -> HttpRouteMatch -> ShowS
$cshowsPrec :: Int -> HttpRouteMatch -> ShowS
Prelude.Show, forall x. Rep HttpRouteMatch x -> HttpRouteMatch
forall x. HttpRouteMatch -> Rep HttpRouteMatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HttpRouteMatch x -> HttpRouteMatch
$cfrom :: forall x. HttpRouteMatch -> Rep HttpRouteMatch x
Prelude.Generic)

-- |
-- Create a value of 'HttpRouteMatch' 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', 'httpRouteMatch_headers' - The client request headers to match on.
--
-- 'method', 'httpRouteMatch_method' - The client request method to match on. Specify only one.
--
-- 'path', 'httpRouteMatch_path' - The client request path to match on.
--
-- 'port', 'httpRouteMatch_port' - The port number to match on.
--
-- 'prefix', 'httpRouteMatch_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', 'httpRouteMatch_queryParameters' - The client request query parameters to match on.
--
-- 'scheme', 'httpRouteMatch_scheme' - The client request scheme to match on. Specify only one. Applicable only
-- for HTTP2 routes.
newHttpRouteMatch ::
  HttpRouteMatch
newHttpRouteMatch :: HttpRouteMatch
newHttpRouteMatch =
  HttpRouteMatch'
    { $sel:headers:HttpRouteMatch' :: Maybe (NonEmpty HttpRouteHeader)
headers = forall a. Maybe a
Prelude.Nothing,
      $sel:method:HttpRouteMatch' :: Maybe HttpMethod
method = forall a. Maybe a
Prelude.Nothing,
      $sel:path:HttpRouteMatch' :: Maybe HttpPathMatch
path = forall a. Maybe a
Prelude.Nothing,
      $sel:port:HttpRouteMatch' :: Maybe Natural
port = forall a. Maybe a
Prelude.Nothing,
      $sel:prefix:HttpRouteMatch' :: Maybe Text
prefix = forall a. Maybe a
Prelude.Nothing,
      $sel:queryParameters:HttpRouteMatch' :: Maybe (NonEmpty HttpQueryParameter)
queryParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:scheme:HttpRouteMatch' :: Maybe HttpScheme
scheme = forall a. Maybe a
Prelude.Nothing
    }

-- | The client request headers to match on.
httpRouteMatch_headers :: Lens.Lens' HttpRouteMatch (Prelude.Maybe (Prelude.NonEmpty HttpRouteHeader))
httpRouteMatch_headers :: Lens' HttpRouteMatch (Maybe (NonEmpty HttpRouteHeader))
httpRouteMatch_headers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpRouteMatch' {Maybe (NonEmpty HttpRouteHeader)
headers :: Maybe (NonEmpty HttpRouteHeader)
$sel:headers:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpRouteHeader)
headers} -> Maybe (NonEmpty HttpRouteHeader)
headers) (\s :: HttpRouteMatch
s@HttpRouteMatch' {} Maybe (NonEmpty HttpRouteHeader)
a -> HttpRouteMatch
s {$sel:headers:HttpRouteMatch' :: Maybe (NonEmpty HttpRouteHeader)
headers = Maybe (NonEmpty HttpRouteHeader)
a} :: HttpRouteMatch) 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 client request method to match on. Specify only one.
httpRouteMatch_method :: Lens.Lens' HttpRouteMatch (Prelude.Maybe HttpMethod)
httpRouteMatch_method :: Lens' HttpRouteMatch (Maybe HttpMethod)
httpRouteMatch_method = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpRouteMatch' {Maybe HttpMethod
method :: Maybe HttpMethod
$sel:method:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpMethod
method} -> Maybe HttpMethod
method) (\s :: HttpRouteMatch
s@HttpRouteMatch' {} Maybe HttpMethod
a -> HttpRouteMatch
s {$sel:method:HttpRouteMatch' :: Maybe HttpMethod
method = Maybe HttpMethod
a} :: HttpRouteMatch)

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

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

-- | 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@.
httpRouteMatch_prefix :: Lens.Lens' HttpRouteMatch (Prelude.Maybe Prelude.Text)
httpRouteMatch_prefix :: Lens' HttpRouteMatch (Maybe Text)
httpRouteMatch_prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpRouteMatch' {Maybe Text
prefix :: Maybe Text
$sel:prefix:HttpRouteMatch' :: HttpRouteMatch -> Maybe Text
prefix} -> Maybe Text
prefix) (\s :: HttpRouteMatch
s@HttpRouteMatch' {} Maybe Text
a -> HttpRouteMatch
s {$sel:prefix:HttpRouteMatch' :: Maybe Text
prefix = Maybe Text
a} :: HttpRouteMatch)

-- | The client request query parameters to match on.
httpRouteMatch_queryParameters :: Lens.Lens' HttpRouteMatch (Prelude.Maybe (Prelude.NonEmpty HttpQueryParameter))
httpRouteMatch_queryParameters :: Lens' HttpRouteMatch (Maybe (NonEmpty HttpQueryParameter))
httpRouteMatch_queryParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpRouteMatch' {Maybe (NonEmpty HttpQueryParameter)
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
$sel:queryParameters:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
queryParameters} -> Maybe (NonEmpty HttpQueryParameter)
queryParameters) (\s :: HttpRouteMatch
s@HttpRouteMatch' {} Maybe (NonEmpty HttpQueryParameter)
a -> HttpRouteMatch
s {$sel:queryParameters:HttpRouteMatch' :: Maybe (NonEmpty HttpQueryParameter)
queryParameters = Maybe (NonEmpty HttpQueryParameter)
a} :: HttpRouteMatch) 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 client request scheme to match on. Specify only one. Applicable only
-- for HTTP2 routes.
httpRouteMatch_scheme :: Lens.Lens' HttpRouteMatch (Prelude.Maybe HttpScheme)
httpRouteMatch_scheme :: Lens' HttpRouteMatch (Maybe HttpScheme)
httpRouteMatch_scheme = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpRouteMatch' {Maybe HttpScheme
scheme :: Maybe HttpScheme
$sel:scheme:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpScheme
scheme} -> Maybe HttpScheme
scheme) (\s :: HttpRouteMatch
s@HttpRouteMatch' {} Maybe HttpScheme
a -> HttpRouteMatch
s {$sel:scheme:HttpRouteMatch' :: Maybe HttpScheme
scheme = Maybe HttpScheme
a} :: HttpRouteMatch)

instance Data.FromJSON HttpRouteMatch where
  parseJSON :: Value -> Parser HttpRouteMatch
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HttpRouteMatch"
      ( \Object
x ->
          Maybe (NonEmpty HttpRouteHeader)
-> Maybe HttpMethod
-> Maybe HttpPathMatch
-> Maybe Natural
-> Maybe Text
-> Maybe (NonEmpty HttpQueryParameter)
-> Maybe HttpScheme
-> HttpRouteMatch
HttpRouteMatch'
            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
"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")
            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
"scheme")
      )

instance Prelude.Hashable HttpRouteMatch where
  hashWithSalt :: Int -> HttpRouteMatch -> Int
hashWithSalt Int
_salt HttpRouteMatch' {Maybe Natural
Maybe (NonEmpty HttpRouteHeader)
Maybe (NonEmpty HttpQueryParameter)
Maybe Text
Maybe HttpMethod
Maybe HttpPathMatch
Maybe HttpScheme
scheme :: Maybe HttpScheme
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
prefix :: Maybe Text
port :: Maybe Natural
path :: Maybe HttpPathMatch
method :: Maybe HttpMethod
headers :: Maybe (NonEmpty HttpRouteHeader)
$sel:scheme:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpScheme
$sel:queryParameters:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
$sel:prefix:HttpRouteMatch' :: HttpRouteMatch -> Maybe Text
$sel:port:HttpRouteMatch' :: HttpRouteMatch -> Maybe Natural
$sel:path:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpPathMatch
$sel:method:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpMethod
$sel:headers:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpRouteHeader)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty HttpRouteHeader)
headers
      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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpScheme
scheme

instance Prelude.NFData HttpRouteMatch where
  rnf :: HttpRouteMatch -> ()
rnf HttpRouteMatch' {Maybe Natural
Maybe (NonEmpty HttpRouteHeader)
Maybe (NonEmpty HttpQueryParameter)
Maybe Text
Maybe HttpMethod
Maybe HttpPathMatch
Maybe HttpScheme
scheme :: Maybe HttpScheme
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
prefix :: Maybe Text
port :: Maybe Natural
path :: Maybe HttpPathMatch
method :: Maybe HttpMethod
headers :: Maybe (NonEmpty HttpRouteHeader)
$sel:scheme:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpScheme
$sel:queryParameters:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
$sel:prefix:HttpRouteMatch' :: HttpRouteMatch -> Maybe Text
$sel:port:HttpRouteMatch' :: HttpRouteMatch -> Maybe Natural
$sel:path:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpPathMatch
$sel:method:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpMethod
$sel:headers:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpRouteHeader)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty HttpRouteHeader)
headers
      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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpScheme
scheme

instance Data.ToJSON HttpRouteMatch where
  toJSON :: HttpRouteMatch -> Value
toJSON HttpRouteMatch' {Maybe Natural
Maybe (NonEmpty HttpRouteHeader)
Maybe (NonEmpty HttpQueryParameter)
Maybe Text
Maybe HttpMethod
Maybe HttpPathMatch
Maybe HttpScheme
scheme :: Maybe HttpScheme
queryParameters :: Maybe (NonEmpty HttpQueryParameter)
prefix :: Maybe Text
port :: Maybe Natural
path :: Maybe HttpPathMatch
method :: Maybe HttpMethod
headers :: Maybe (NonEmpty HttpRouteHeader)
$sel:scheme:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpScheme
$sel:queryParameters:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpQueryParameter)
$sel:prefix:HttpRouteMatch' :: HttpRouteMatch -> Maybe Text
$sel:port:HttpRouteMatch' :: HttpRouteMatch -> Maybe Natural
$sel:path:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpPathMatch
$sel:method:HttpRouteMatch' :: HttpRouteMatch -> Maybe HttpMethod
$sel:headers:HttpRouteMatch' :: HttpRouteMatch -> Maybe (NonEmpty HttpRouteHeader)
..} =
    [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 HttpRouteHeader)
headers,
            (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,
            (Key
"scheme" 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 HttpScheme
scheme
          ]
      )