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

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

-- |
-- Module      : Amazonka.GlobalAccelerator.CreateCustomRoutingListener
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create a listener to process inbound connections from clients to a
-- custom routing accelerator. Connections arrive to assigned static IP
-- addresses on the port range that you specify.
module Amazonka.GlobalAccelerator.CreateCustomRoutingListener
  ( -- * Creating a Request
    CreateCustomRoutingListener (..),
    newCreateCustomRoutingListener,

    -- * Request Lenses
    createCustomRoutingListener_acceleratorArn,
    createCustomRoutingListener_portRanges,
    createCustomRoutingListener_idempotencyToken,

    -- * Destructuring the Response
    CreateCustomRoutingListenerResponse (..),
    newCreateCustomRoutingListenerResponse,

    -- * Response Lenses
    createCustomRoutingListenerResponse_listener,
    createCustomRoutingListenerResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GlobalAccelerator.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateCustomRoutingListener' smart constructor.
data CreateCustomRoutingListener = CreateCustomRoutingListener'
  { -- | The Amazon Resource Name (ARN) of the accelerator for a custom routing
    -- listener.
    CreateCustomRoutingListener -> Text
acceleratorArn :: Prelude.Text,
    -- | The port range to support for connections from clients to your
    -- accelerator.
    --
    -- Separately, you set port ranges for endpoints. For more information, see
    -- <https://docs.aws.amazon.com/global-accelerator/latest/dg/about-custom-routing-endpoints.html About endpoints for custom routing accelerators>.
    CreateCustomRoutingListener -> NonEmpty PortRange
portRanges :: Prelude.NonEmpty PortRange,
    -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency—that is, the uniqueness—of the request.
    CreateCustomRoutingListener -> Text
idempotencyToken :: Prelude.Text
  }
  deriving (CreateCustomRoutingListener -> CreateCustomRoutingListener -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCustomRoutingListener -> CreateCustomRoutingListener -> Bool
$c/= :: CreateCustomRoutingListener -> CreateCustomRoutingListener -> Bool
== :: CreateCustomRoutingListener -> CreateCustomRoutingListener -> Bool
$c== :: CreateCustomRoutingListener -> CreateCustomRoutingListener -> Bool
Prelude.Eq, ReadPrec [CreateCustomRoutingListener]
ReadPrec CreateCustomRoutingListener
Int -> ReadS CreateCustomRoutingListener
ReadS [CreateCustomRoutingListener]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCustomRoutingListener]
$creadListPrec :: ReadPrec [CreateCustomRoutingListener]
readPrec :: ReadPrec CreateCustomRoutingListener
$creadPrec :: ReadPrec CreateCustomRoutingListener
readList :: ReadS [CreateCustomRoutingListener]
$creadList :: ReadS [CreateCustomRoutingListener]
readsPrec :: Int -> ReadS CreateCustomRoutingListener
$creadsPrec :: Int -> ReadS CreateCustomRoutingListener
Prelude.Read, Int -> CreateCustomRoutingListener -> ShowS
[CreateCustomRoutingListener] -> ShowS
CreateCustomRoutingListener -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCustomRoutingListener] -> ShowS
$cshowList :: [CreateCustomRoutingListener] -> ShowS
show :: CreateCustomRoutingListener -> String
$cshow :: CreateCustomRoutingListener -> String
showsPrec :: Int -> CreateCustomRoutingListener -> ShowS
$cshowsPrec :: Int -> CreateCustomRoutingListener -> ShowS
Prelude.Show, forall x.
Rep CreateCustomRoutingListener x -> CreateCustomRoutingListener
forall x.
CreateCustomRoutingListener -> Rep CreateCustomRoutingListener x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCustomRoutingListener x -> CreateCustomRoutingListener
$cfrom :: forall x.
CreateCustomRoutingListener -> Rep CreateCustomRoutingListener x
Prelude.Generic)

-- |
-- Create a value of 'CreateCustomRoutingListener' 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:
--
-- 'acceleratorArn', 'createCustomRoutingListener_acceleratorArn' - The Amazon Resource Name (ARN) of the accelerator for a custom routing
-- listener.
--
-- 'portRanges', 'createCustomRoutingListener_portRanges' - The port range to support for connections from clients to your
-- accelerator.
--
-- Separately, you set port ranges for endpoints. For more information, see
-- <https://docs.aws.amazon.com/global-accelerator/latest/dg/about-custom-routing-endpoints.html About endpoints for custom routing accelerators>.
--
-- 'idempotencyToken', 'createCustomRoutingListener_idempotencyToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency—that is, the uniqueness—of the request.
newCreateCustomRoutingListener ::
  -- | 'acceleratorArn'
  Prelude.Text ->
  -- | 'portRanges'
  Prelude.NonEmpty PortRange ->
  -- | 'idempotencyToken'
  Prelude.Text ->
  CreateCustomRoutingListener
newCreateCustomRoutingListener :: Text -> NonEmpty PortRange -> Text -> CreateCustomRoutingListener
newCreateCustomRoutingListener
  Text
pAcceleratorArn_
  NonEmpty PortRange
pPortRanges_
  Text
pIdempotencyToken_ =
    CreateCustomRoutingListener'
      { $sel:acceleratorArn:CreateCustomRoutingListener' :: Text
acceleratorArn =
          Text
pAcceleratorArn_,
        $sel:portRanges:CreateCustomRoutingListener' :: NonEmpty PortRange
portRanges = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty PortRange
pPortRanges_,
        $sel:idempotencyToken:CreateCustomRoutingListener' :: Text
idempotencyToken = Text
pIdempotencyToken_
      }

-- | The Amazon Resource Name (ARN) of the accelerator for a custom routing
-- listener.
createCustomRoutingListener_acceleratorArn :: Lens.Lens' CreateCustomRoutingListener Prelude.Text
createCustomRoutingListener_acceleratorArn :: Lens' CreateCustomRoutingListener Text
createCustomRoutingListener_acceleratorArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomRoutingListener' {Text
acceleratorArn :: Text
$sel:acceleratorArn:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
acceleratorArn} -> Text
acceleratorArn) (\s :: CreateCustomRoutingListener
s@CreateCustomRoutingListener' {} Text
a -> CreateCustomRoutingListener
s {$sel:acceleratorArn:CreateCustomRoutingListener' :: Text
acceleratorArn = Text
a} :: CreateCustomRoutingListener)

-- | The port range to support for connections from clients to your
-- accelerator.
--
-- Separately, you set port ranges for endpoints. For more information, see
-- <https://docs.aws.amazon.com/global-accelerator/latest/dg/about-custom-routing-endpoints.html About endpoints for custom routing accelerators>.
createCustomRoutingListener_portRanges :: Lens.Lens' CreateCustomRoutingListener (Prelude.NonEmpty PortRange)
createCustomRoutingListener_portRanges :: Lens' CreateCustomRoutingListener (NonEmpty PortRange)
createCustomRoutingListener_portRanges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomRoutingListener' {NonEmpty PortRange
portRanges :: NonEmpty PortRange
$sel:portRanges:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> NonEmpty PortRange
portRanges} -> NonEmpty PortRange
portRanges) (\s :: CreateCustomRoutingListener
s@CreateCustomRoutingListener' {} NonEmpty PortRange
a -> CreateCustomRoutingListener
s {$sel:portRanges:CreateCustomRoutingListener' :: NonEmpty PortRange
portRanges = NonEmpty PortRange
a} :: CreateCustomRoutingListener) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency—that is, the uniqueness—of the request.
createCustomRoutingListener_idempotencyToken :: Lens.Lens' CreateCustomRoutingListener Prelude.Text
createCustomRoutingListener_idempotencyToken :: Lens' CreateCustomRoutingListener Text
createCustomRoutingListener_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomRoutingListener' {Text
idempotencyToken :: Text
$sel:idempotencyToken:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
idempotencyToken} -> Text
idempotencyToken) (\s :: CreateCustomRoutingListener
s@CreateCustomRoutingListener' {} Text
a -> CreateCustomRoutingListener
s {$sel:idempotencyToken:CreateCustomRoutingListener' :: Text
idempotencyToken = Text
a} :: CreateCustomRoutingListener)

instance Core.AWSRequest CreateCustomRoutingListener where
  type
    AWSResponse CreateCustomRoutingListener =
      CreateCustomRoutingListenerResponse
  request :: (Service -> Service)
-> CreateCustomRoutingListener
-> Request CreateCustomRoutingListener
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateCustomRoutingListener
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateCustomRoutingListener)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe CustomRoutingListener
-> Int -> CreateCustomRoutingListenerResponse
CreateCustomRoutingListenerResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Listener")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateCustomRoutingListener where
  hashWithSalt :: Int -> CreateCustomRoutingListener -> Int
hashWithSalt Int
_salt CreateCustomRoutingListener' {NonEmpty PortRange
Text
idempotencyToken :: Text
portRanges :: NonEmpty PortRange
acceleratorArn :: Text
$sel:idempotencyToken:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
$sel:portRanges:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> NonEmpty PortRange
$sel:acceleratorArn:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
acceleratorArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty PortRange
portRanges
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
idempotencyToken

instance Prelude.NFData CreateCustomRoutingListener where
  rnf :: CreateCustomRoutingListener -> ()
rnf CreateCustomRoutingListener' {NonEmpty PortRange
Text
idempotencyToken :: Text
portRanges :: NonEmpty PortRange
acceleratorArn :: Text
$sel:idempotencyToken:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
$sel:portRanges:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> NonEmpty PortRange
$sel:acceleratorArn:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
acceleratorArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty PortRange
portRanges
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
idempotencyToken

instance Data.ToHeaders CreateCustomRoutingListener where
  toHeaders :: CreateCustomRoutingListener -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"GlobalAccelerator_V20180706.CreateCustomRoutingListener" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateCustomRoutingListener where
  toJSON :: CreateCustomRoutingListener -> Value
toJSON CreateCustomRoutingListener' {NonEmpty PortRange
Text
idempotencyToken :: Text
portRanges :: NonEmpty PortRange
acceleratorArn :: Text
$sel:idempotencyToken:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
$sel:portRanges:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> NonEmpty PortRange
$sel:acceleratorArn:CreateCustomRoutingListener' :: CreateCustomRoutingListener -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"AcceleratorArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
acceleratorArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"PortRanges" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty PortRange
portRanges),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"IdempotencyToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
idempotencyToken)
          ]
      )

instance Data.ToPath CreateCustomRoutingListener where
  toPath :: CreateCustomRoutingListener -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery CreateCustomRoutingListener where
  toQuery :: CreateCustomRoutingListener -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newCreateCustomRoutingListenerResponse' smart constructor.
data CreateCustomRoutingListenerResponse = CreateCustomRoutingListenerResponse'
  { -- | The listener that you\'ve created for a custom routing accelerator.
    CreateCustomRoutingListenerResponse -> Maybe CustomRoutingListener
listener :: Prelude.Maybe CustomRoutingListener,
    -- | The response's http status code.
    CreateCustomRoutingListenerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateCustomRoutingListenerResponse
-> CreateCustomRoutingListenerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCustomRoutingListenerResponse
-> CreateCustomRoutingListenerResponse -> Bool
$c/= :: CreateCustomRoutingListenerResponse
-> CreateCustomRoutingListenerResponse -> Bool
== :: CreateCustomRoutingListenerResponse
-> CreateCustomRoutingListenerResponse -> Bool
$c== :: CreateCustomRoutingListenerResponse
-> CreateCustomRoutingListenerResponse -> Bool
Prelude.Eq, ReadPrec [CreateCustomRoutingListenerResponse]
ReadPrec CreateCustomRoutingListenerResponse
Int -> ReadS CreateCustomRoutingListenerResponse
ReadS [CreateCustomRoutingListenerResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCustomRoutingListenerResponse]
$creadListPrec :: ReadPrec [CreateCustomRoutingListenerResponse]
readPrec :: ReadPrec CreateCustomRoutingListenerResponse
$creadPrec :: ReadPrec CreateCustomRoutingListenerResponse
readList :: ReadS [CreateCustomRoutingListenerResponse]
$creadList :: ReadS [CreateCustomRoutingListenerResponse]
readsPrec :: Int -> ReadS CreateCustomRoutingListenerResponse
$creadsPrec :: Int -> ReadS CreateCustomRoutingListenerResponse
Prelude.Read, Int -> CreateCustomRoutingListenerResponse -> ShowS
[CreateCustomRoutingListenerResponse] -> ShowS
CreateCustomRoutingListenerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCustomRoutingListenerResponse] -> ShowS
$cshowList :: [CreateCustomRoutingListenerResponse] -> ShowS
show :: CreateCustomRoutingListenerResponse -> String
$cshow :: CreateCustomRoutingListenerResponse -> String
showsPrec :: Int -> CreateCustomRoutingListenerResponse -> ShowS
$cshowsPrec :: Int -> CreateCustomRoutingListenerResponse -> ShowS
Prelude.Show, forall x.
Rep CreateCustomRoutingListenerResponse x
-> CreateCustomRoutingListenerResponse
forall x.
CreateCustomRoutingListenerResponse
-> Rep CreateCustomRoutingListenerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCustomRoutingListenerResponse x
-> CreateCustomRoutingListenerResponse
$cfrom :: forall x.
CreateCustomRoutingListenerResponse
-> Rep CreateCustomRoutingListenerResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateCustomRoutingListenerResponse' 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:
--
-- 'listener', 'createCustomRoutingListenerResponse_listener' - The listener that you\'ve created for a custom routing accelerator.
--
-- 'httpStatus', 'createCustomRoutingListenerResponse_httpStatus' - The response's http status code.
newCreateCustomRoutingListenerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateCustomRoutingListenerResponse
newCreateCustomRoutingListenerResponse :: Int -> CreateCustomRoutingListenerResponse
newCreateCustomRoutingListenerResponse Int
pHttpStatus_ =
  CreateCustomRoutingListenerResponse'
    { $sel:listener:CreateCustomRoutingListenerResponse' :: Maybe CustomRoutingListener
listener =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateCustomRoutingListenerResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The listener that you\'ve created for a custom routing accelerator.
createCustomRoutingListenerResponse_listener :: Lens.Lens' CreateCustomRoutingListenerResponse (Prelude.Maybe CustomRoutingListener)
createCustomRoutingListenerResponse_listener :: Lens'
  CreateCustomRoutingListenerResponse (Maybe CustomRoutingListener)
createCustomRoutingListenerResponse_listener = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomRoutingListenerResponse' {Maybe CustomRoutingListener
listener :: Maybe CustomRoutingListener
$sel:listener:CreateCustomRoutingListenerResponse' :: CreateCustomRoutingListenerResponse -> Maybe CustomRoutingListener
listener} -> Maybe CustomRoutingListener
listener) (\s :: CreateCustomRoutingListenerResponse
s@CreateCustomRoutingListenerResponse' {} Maybe CustomRoutingListener
a -> CreateCustomRoutingListenerResponse
s {$sel:listener:CreateCustomRoutingListenerResponse' :: Maybe CustomRoutingListener
listener = Maybe CustomRoutingListener
a} :: CreateCustomRoutingListenerResponse)

-- | The response's http status code.
createCustomRoutingListenerResponse_httpStatus :: Lens.Lens' CreateCustomRoutingListenerResponse Prelude.Int
createCustomRoutingListenerResponse_httpStatus :: Lens' CreateCustomRoutingListenerResponse Int
createCustomRoutingListenerResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCustomRoutingListenerResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateCustomRoutingListenerResponse' :: CreateCustomRoutingListenerResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateCustomRoutingListenerResponse
s@CreateCustomRoutingListenerResponse' {} Int
a -> CreateCustomRoutingListenerResponse
s {$sel:httpStatus:CreateCustomRoutingListenerResponse' :: Int
httpStatus = Int
a} :: CreateCustomRoutingListenerResponse)

instance
  Prelude.NFData
    CreateCustomRoutingListenerResponse
  where
  rnf :: CreateCustomRoutingListenerResponse -> ()
rnf CreateCustomRoutingListenerResponse' {Int
Maybe CustomRoutingListener
httpStatus :: Int
listener :: Maybe CustomRoutingListener
$sel:httpStatus:CreateCustomRoutingListenerResponse' :: CreateCustomRoutingListenerResponse -> Int
$sel:listener:CreateCustomRoutingListenerResponse' :: CreateCustomRoutingListenerResponse -> Maybe CustomRoutingListener
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomRoutingListener
listener
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus