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

import Amazonka.AppMesh.Types.HealthCheckPolicy
import Amazonka.AppMesh.Types.ListenerTimeout
import Amazonka.AppMesh.Types.ListenerTls
import Amazonka.AppMesh.Types.OutlierDetection
import Amazonka.AppMesh.Types.PortMapping
import Amazonka.AppMesh.Types.VirtualNodeConnectionPool
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 a listener for a virtual node.
--
-- /See:/ 'newListener' smart constructor.
data Listener = Listener'
  { -- | The connection pool information for the listener.
    Listener -> Maybe VirtualNodeConnectionPool
connectionPool :: Prelude.Maybe VirtualNodeConnectionPool,
    -- | The health check information for the listener.
    Listener -> Maybe HealthCheckPolicy
healthCheck :: Prelude.Maybe HealthCheckPolicy,
    -- | The outlier detection information for the listener.
    Listener -> Maybe OutlierDetection
outlierDetection :: Prelude.Maybe OutlierDetection,
    -- | An object that represents timeouts for different protocols.
    Listener -> Maybe ListenerTimeout
timeout :: Prelude.Maybe ListenerTimeout,
    -- | A reference to an object that represents the Transport Layer Security
    -- (TLS) properties for a listener.
    Listener -> Maybe ListenerTls
tls :: Prelude.Maybe ListenerTls,
    -- | The port mapping information for the listener.
    Listener -> PortMapping
portMapping :: PortMapping
  }
  deriving (Listener -> Listener -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Listener -> Listener -> Bool
$c/= :: Listener -> Listener -> Bool
== :: Listener -> Listener -> Bool
$c== :: Listener -> Listener -> Bool
Prelude.Eq, ReadPrec [Listener]
ReadPrec Listener
Int -> ReadS Listener
ReadS [Listener]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Listener]
$creadListPrec :: ReadPrec [Listener]
readPrec :: ReadPrec Listener
$creadPrec :: ReadPrec Listener
readList :: ReadS [Listener]
$creadList :: ReadS [Listener]
readsPrec :: Int -> ReadS Listener
$creadsPrec :: Int -> ReadS Listener
Prelude.Read, Int -> Listener -> ShowS
[Listener] -> ShowS
Listener -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Listener] -> ShowS
$cshowList :: [Listener] -> ShowS
show :: Listener -> String
$cshow :: Listener -> String
showsPrec :: Int -> Listener -> ShowS
$cshowsPrec :: Int -> Listener -> ShowS
Prelude.Show, forall x. Rep Listener x -> Listener
forall x. Listener -> Rep Listener x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Listener x -> Listener
$cfrom :: forall x. Listener -> Rep Listener x
Prelude.Generic)

-- |
-- Create a value of 'Listener' 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:
--
-- 'connectionPool', 'listener_connectionPool' - The connection pool information for the listener.
--
-- 'healthCheck', 'listener_healthCheck' - The health check information for the listener.
--
-- 'outlierDetection', 'listener_outlierDetection' - The outlier detection information for the listener.
--
-- 'timeout', 'listener_timeout' - An object that represents timeouts for different protocols.
--
-- 'tls', 'listener_tls' - A reference to an object that represents the Transport Layer Security
-- (TLS) properties for a listener.
--
-- 'portMapping', 'listener_portMapping' - The port mapping information for the listener.
newListener ::
  -- | 'portMapping'
  PortMapping ->
  Listener
newListener :: PortMapping -> Listener
newListener PortMapping
pPortMapping_ =
  Listener'
    { $sel:connectionPool:Listener' :: Maybe VirtualNodeConnectionPool
connectionPool = forall a. Maybe a
Prelude.Nothing,
      $sel:healthCheck:Listener' :: Maybe HealthCheckPolicy
healthCheck = forall a. Maybe a
Prelude.Nothing,
      $sel:outlierDetection:Listener' :: Maybe OutlierDetection
outlierDetection = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:Listener' :: Maybe ListenerTimeout
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:tls:Listener' :: Maybe ListenerTls
tls = forall a. Maybe a
Prelude.Nothing,
      $sel:portMapping:Listener' :: PortMapping
portMapping = PortMapping
pPortMapping_
    }

-- | The connection pool information for the listener.
listener_connectionPool :: Lens.Lens' Listener (Prelude.Maybe VirtualNodeConnectionPool)
listener_connectionPool :: Lens' Listener (Maybe VirtualNodeConnectionPool)
listener_connectionPool = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Listener' {Maybe VirtualNodeConnectionPool
connectionPool :: Maybe VirtualNodeConnectionPool
$sel:connectionPool:Listener' :: Listener -> Maybe VirtualNodeConnectionPool
connectionPool} -> Maybe VirtualNodeConnectionPool
connectionPool) (\s :: Listener
s@Listener' {} Maybe VirtualNodeConnectionPool
a -> Listener
s {$sel:connectionPool:Listener' :: Maybe VirtualNodeConnectionPool
connectionPool = Maybe VirtualNodeConnectionPool
a} :: Listener)

-- | The health check information for the listener.
listener_healthCheck :: Lens.Lens' Listener (Prelude.Maybe HealthCheckPolicy)
listener_healthCheck :: Lens' Listener (Maybe HealthCheckPolicy)
listener_healthCheck = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Listener' {Maybe HealthCheckPolicy
healthCheck :: Maybe HealthCheckPolicy
$sel:healthCheck:Listener' :: Listener -> Maybe HealthCheckPolicy
healthCheck} -> Maybe HealthCheckPolicy
healthCheck) (\s :: Listener
s@Listener' {} Maybe HealthCheckPolicy
a -> Listener
s {$sel:healthCheck:Listener' :: Maybe HealthCheckPolicy
healthCheck = Maybe HealthCheckPolicy
a} :: Listener)

-- | The outlier detection information for the listener.
listener_outlierDetection :: Lens.Lens' Listener (Prelude.Maybe OutlierDetection)
listener_outlierDetection :: Lens' Listener (Maybe OutlierDetection)
listener_outlierDetection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Listener' {Maybe OutlierDetection
outlierDetection :: Maybe OutlierDetection
$sel:outlierDetection:Listener' :: Listener -> Maybe OutlierDetection
outlierDetection} -> Maybe OutlierDetection
outlierDetection) (\s :: Listener
s@Listener' {} Maybe OutlierDetection
a -> Listener
s {$sel:outlierDetection:Listener' :: Maybe OutlierDetection
outlierDetection = Maybe OutlierDetection
a} :: Listener)

-- | An object that represents timeouts for different protocols.
listener_timeout :: Lens.Lens' Listener (Prelude.Maybe ListenerTimeout)
listener_timeout :: Lens' Listener (Maybe ListenerTimeout)
listener_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Listener' {Maybe ListenerTimeout
timeout :: Maybe ListenerTimeout
$sel:timeout:Listener' :: Listener -> Maybe ListenerTimeout
timeout} -> Maybe ListenerTimeout
timeout) (\s :: Listener
s@Listener' {} Maybe ListenerTimeout
a -> Listener
s {$sel:timeout:Listener' :: Maybe ListenerTimeout
timeout = Maybe ListenerTimeout
a} :: Listener)

-- | A reference to an object that represents the Transport Layer Security
-- (TLS) properties for a listener.
listener_tls :: Lens.Lens' Listener (Prelude.Maybe ListenerTls)
listener_tls :: Lens' Listener (Maybe ListenerTls)
listener_tls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Listener' {Maybe ListenerTls
tls :: Maybe ListenerTls
$sel:tls:Listener' :: Listener -> Maybe ListenerTls
tls} -> Maybe ListenerTls
tls) (\s :: Listener
s@Listener' {} Maybe ListenerTls
a -> Listener
s {$sel:tls:Listener' :: Maybe ListenerTls
tls = Maybe ListenerTls
a} :: Listener)

-- | The port mapping information for the listener.
listener_portMapping :: Lens.Lens' Listener PortMapping
listener_portMapping :: Lens' Listener PortMapping
listener_portMapping = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Listener' {PortMapping
portMapping :: PortMapping
$sel:portMapping:Listener' :: Listener -> PortMapping
portMapping} -> PortMapping
portMapping) (\s :: Listener
s@Listener' {} PortMapping
a -> Listener
s {$sel:portMapping:Listener' :: PortMapping
portMapping = PortMapping
a} :: Listener)

instance Data.FromJSON Listener where
  parseJSON :: Value -> Parser Listener
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Listener"
      ( \Object
x ->
          Maybe VirtualNodeConnectionPool
-> Maybe HealthCheckPolicy
-> Maybe OutlierDetection
-> Maybe ListenerTimeout
-> Maybe ListenerTls
-> PortMapping
-> Listener
Listener'
            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
"connectionPool")
            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
"healthCheck")
            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
"outlierDetection")
            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
"timeout")
            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
"tls")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"portMapping")
      )

instance Prelude.Hashable Listener where
  hashWithSalt :: Int -> Listener -> Int
hashWithSalt Int
_salt Listener' {Maybe OutlierDetection
Maybe HealthCheckPolicy
Maybe ListenerTimeout
Maybe ListenerTls
Maybe VirtualNodeConnectionPool
PortMapping
portMapping :: PortMapping
tls :: Maybe ListenerTls
timeout :: Maybe ListenerTimeout
outlierDetection :: Maybe OutlierDetection
healthCheck :: Maybe HealthCheckPolicy
connectionPool :: Maybe VirtualNodeConnectionPool
$sel:portMapping:Listener' :: Listener -> PortMapping
$sel:tls:Listener' :: Listener -> Maybe ListenerTls
$sel:timeout:Listener' :: Listener -> Maybe ListenerTimeout
$sel:outlierDetection:Listener' :: Listener -> Maybe OutlierDetection
$sel:healthCheck:Listener' :: Listener -> Maybe HealthCheckPolicy
$sel:connectionPool:Listener' :: Listener -> Maybe VirtualNodeConnectionPool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VirtualNodeConnectionPool
connectionPool
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HealthCheckPolicy
healthCheck
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OutlierDetection
outlierDetection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ListenerTimeout
timeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ListenerTls
tls
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PortMapping
portMapping

instance Prelude.NFData Listener where
  rnf :: Listener -> ()
rnf Listener' {Maybe OutlierDetection
Maybe HealthCheckPolicy
Maybe ListenerTimeout
Maybe ListenerTls
Maybe VirtualNodeConnectionPool
PortMapping
portMapping :: PortMapping
tls :: Maybe ListenerTls
timeout :: Maybe ListenerTimeout
outlierDetection :: Maybe OutlierDetection
healthCheck :: Maybe HealthCheckPolicy
connectionPool :: Maybe VirtualNodeConnectionPool
$sel:portMapping:Listener' :: Listener -> PortMapping
$sel:tls:Listener' :: Listener -> Maybe ListenerTls
$sel:timeout:Listener' :: Listener -> Maybe ListenerTimeout
$sel:outlierDetection:Listener' :: Listener -> Maybe OutlierDetection
$sel:healthCheck:Listener' :: Listener -> Maybe HealthCheckPolicy
$sel:connectionPool:Listener' :: Listener -> Maybe VirtualNodeConnectionPool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe VirtualNodeConnectionPool
connectionPool
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HealthCheckPolicy
healthCheck
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OutlierDetection
outlierDetection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ListenerTimeout
timeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ListenerTls
tls
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf PortMapping
portMapping

instance Data.ToJSON Listener where
  toJSON :: Listener -> Value
toJSON Listener' {Maybe OutlierDetection
Maybe HealthCheckPolicy
Maybe ListenerTimeout
Maybe ListenerTls
Maybe VirtualNodeConnectionPool
PortMapping
portMapping :: PortMapping
tls :: Maybe ListenerTls
timeout :: Maybe ListenerTimeout
outlierDetection :: Maybe OutlierDetection
healthCheck :: Maybe HealthCheckPolicy
connectionPool :: Maybe VirtualNodeConnectionPool
$sel:portMapping:Listener' :: Listener -> PortMapping
$sel:tls:Listener' :: Listener -> Maybe ListenerTls
$sel:timeout:Listener' :: Listener -> Maybe ListenerTimeout
$sel:outlierDetection:Listener' :: Listener -> Maybe OutlierDetection
$sel:healthCheck:Listener' :: Listener -> Maybe HealthCheckPolicy
$sel:connectionPool:Listener' :: Listener -> Maybe VirtualNodeConnectionPool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"connectionPool" 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 VirtualNodeConnectionPool
connectionPool,
            (Key
"healthCheck" 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 HealthCheckPolicy
healthCheck,
            (Key
"outlierDetection" 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 OutlierDetection
outlierDetection,
            (Key
"timeout" 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 ListenerTimeout
timeout,
            (Key
"tls" 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 ListenerTls
tls,
            forall a. a -> Maybe a
Prelude.Just (Key
"portMapping" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= PortMapping
portMapping)
          ]
      )