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

import Amazonka.AppMesh.Types.GrpcTimeout
import Amazonka.AppMesh.Types.HttpTimeout
import Amazonka.AppMesh.Types.TcpTimeout
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 timeouts for different protocols.
--
-- /See:/ 'newListenerTimeout' smart constructor.
data ListenerTimeout = ListenerTimeout'
  { -- | An object that represents types of timeouts.
    ListenerTimeout -> Maybe GrpcTimeout
grpc :: Prelude.Maybe GrpcTimeout,
    -- | An object that represents types of timeouts.
    ListenerTimeout -> Maybe HttpTimeout
http :: Prelude.Maybe HttpTimeout,
    -- | An object that represents types of timeouts.
    ListenerTimeout -> Maybe HttpTimeout
http2 :: Prelude.Maybe HttpTimeout,
    -- | An object that represents types of timeouts.
    ListenerTimeout -> Maybe TcpTimeout
tcp :: Prelude.Maybe TcpTimeout
  }
  deriving (ListenerTimeout -> ListenerTimeout -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListenerTimeout -> ListenerTimeout -> Bool
$c/= :: ListenerTimeout -> ListenerTimeout -> Bool
== :: ListenerTimeout -> ListenerTimeout -> Bool
$c== :: ListenerTimeout -> ListenerTimeout -> Bool
Prelude.Eq, ReadPrec [ListenerTimeout]
ReadPrec ListenerTimeout
Int -> ReadS ListenerTimeout
ReadS [ListenerTimeout]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListenerTimeout]
$creadListPrec :: ReadPrec [ListenerTimeout]
readPrec :: ReadPrec ListenerTimeout
$creadPrec :: ReadPrec ListenerTimeout
readList :: ReadS [ListenerTimeout]
$creadList :: ReadS [ListenerTimeout]
readsPrec :: Int -> ReadS ListenerTimeout
$creadsPrec :: Int -> ReadS ListenerTimeout
Prelude.Read, Int -> ListenerTimeout -> ShowS
[ListenerTimeout] -> ShowS
ListenerTimeout -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListenerTimeout] -> ShowS
$cshowList :: [ListenerTimeout] -> ShowS
show :: ListenerTimeout -> String
$cshow :: ListenerTimeout -> String
showsPrec :: Int -> ListenerTimeout -> ShowS
$cshowsPrec :: Int -> ListenerTimeout -> ShowS
Prelude.Show, forall x. Rep ListenerTimeout x -> ListenerTimeout
forall x. ListenerTimeout -> Rep ListenerTimeout x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListenerTimeout x -> ListenerTimeout
$cfrom :: forall x. ListenerTimeout -> Rep ListenerTimeout x
Prelude.Generic)

-- |
-- Create a value of 'ListenerTimeout' 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:
--
-- 'grpc', 'listenerTimeout_grpc' - An object that represents types of timeouts.
--
-- 'http', 'listenerTimeout_http' - An object that represents types of timeouts.
--
-- 'http2', 'listenerTimeout_http2' - An object that represents types of timeouts.
--
-- 'tcp', 'listenerTimeout_tcp' - An object that represents types of timeouts.
newListenerTimeout ::
  ListenerTimeout
newListenerTimeout :: ListenerTimeout
newListenerTimeout =
  ListenerTimeout'
    { $sel:grpc:ListenerTimeout' :: Maybe GrpcTimeout
grpc = forall a. Maybe a
Prelude.Nothing,
      $sel:http:ListenerTimeout' :: Maybe HttpTimeout
http = forall a. Maybe a
Prelude.Nothing,
      $sel:http2:ListenerTimeout' :: Maybe HttpTimeout
http2 = forall a. Maybe a
Prelude.Nothing,
      $sel:tcp:ListenerTimeout' :: Maybe TcpTimeout
tcp = forall a. Maybe a
Prelude.Nothing
    }

-- | An object that represents types of timeouts.
listenerTimeout_grpc :: Lens.Lens' ListenerTimeout (Prelude.Maybe GrpcTimeout)
listenerTimeout_grpc :: Lens' ListenerTimeout (Maybe GrpcTimeout)
listenerTimeout_grpc = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListenerTimeout' {Maybe GrpcTimeout
grpc :: Maybe GrpcTimeout
$sel:grpc:ListenerTimeout' :: ListenerTimeout -> Maybe GrpcTimeout
grpc} -> Maybe GrpcTimeout
grpc) (\s :: ListenerTimeout
s@ListenerTimeout' {} Maybe GrpcTimeout
a -> ListenerTimeout
s {$sel:grpc:ListenerTimeout' :: Maybe GrpcTimeout
grpc = Maybe GrpcTimeout
a} :: ListenerTimeout)

-- | An object that represents types of timeouts.
listenerTimeout_http :: Lens.Lens' ListenerTimeout (Prelude.Maybe HttpTimeout)
listenerTimeout_http :: Lens' ListenerTimeout (Maybe HttpTimeout)
listenerTimeout_http = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListenerTimeout' {Maybe HttpTimeout
http :: Maybe HttpTimeout
$sel:http:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
http} -> Maybe HttpTimeout
http) (\s :: ListenerTimeout
s@ListenerTimeout' {} Maybe HttpTimeout
a -> ListenerTimeout
s {$sel:http:ListenerTimeout' :: Maybe HttpTimeout
http = Maybe HttpTimeout
a} :: ListenerTimeout)

-- | An object that represents types of timeouts.
listenerTimeout_http2 :: Lens.Lens' ListenerTimeout (Prelude.Maybe HttpTimeout)
listenerTimeout_http2 :: Lens' ListenerTimeout (Maybe HttpTimeout)
listenerTimeout_http2 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListenerTimeout' {Maybe HttpTimeout
http2 :: Maybe HttpTimeout
$sel:http2:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
http2} -> Maybe HttpTimeout
http2) (\s :: ListenerTimeout
s@ListenerTimeout' {} Maybe HttpTimeout
a -> ListenerTimeout
s {$sel:http2:ListenerTimeout' :: Maybe HttpTimeout
http2 = Maybe HttpTimeout
a} :: ListenerTimeout)

-- | An object that represents types of timeouts.
listenerTimeout_tcp :: Lens.Lens' ListenerTimeout (Prelude.Maybe TcpTimeout)
listenerTimeout_tcp :: Lens' ListenerTimeout (Maybe TcpTimeout)
listenerTimeout_tcp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListenerTimeout' {Maybe TcpTimeout
tcp :: Maybe TcpTimeout
$sel:tcp:ListenerTimeout' :: ListenerTimeout -> Maybe TcpTimeout
tcp} -> Maybe TcpTimeout
tcp) (\s :: ListenerTimeout
s@ListenerTimeout' {} Maybe TcpTimeout
a -> ListenerTimeout
s {$sel:tcp:ListenerTimeout' :: Maybe TcpTimeout
tcp = Maybe TcpTimeout
a} :: ListenerTimeout)

instance Data.FromJSON ListenerTimeout where
  parseJSON :: Value -> Parser ListenerTimeout
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ListenerTimeout"
      ( \Object
x ->
          Maybe GrpcTimeout
-> Maybe HttpTimeout
-> Maybe HttpTimeout
-> Maybe TcpTimeout
-> ListenerTimeout
ListenerTimeout'
            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
"grpc")
            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
"http")
            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
"http2")
            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
"tcp")
      )

instance Prelude.Hashable ListenerTimeout where
  hashWithSalt :: Int -> ListenerTimeout -> Int
hashWithSalt Int
_salt ListenerTimeout' {Maybe GrpcTimeout
Maybe HttpTimeout
Maybe TcpTimeout
tcp :: Maybe TcpTimeout
http2 :: Maybe HttpTimeout
http :: Maybe HttpTimeout
grpc :: Maybe GrpcTimeout
$sel:tcp:ListenerTimeout' :: ListenerTimeout -> Maybe TcpTimeout
$sel:http2:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
$sel:http:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
$sel:grpc:ListenerTimeout' :: ListenerTimeout -> Maybe GrpcTimeout
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GrpcTimeout
grpc
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpTimeout
http
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpTimeout
http2
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TcpTimeout
tcp

instance Prelude.NFData ListenerTimeout where
  rnf :: ListenerTimeout -> ()
rnf ListenerTimeout' {Maybe GrpcTimeout
Maybe HttpTimeout
Maybe TcpTimeout
tcp :: Maybe TcpTimeout
http2 :: Maybe HttpTimeout
http :: Maybe HttpTimeout
grpc :: Maybe GrpcTimeout
$sel:tcp:ListenerTimeout' :: ListenerTimeout -> Maybe TcpTimeout
$sel:http2:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
$sel:http:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
$sel:grpc:ListenerTimeout' :: ListenerTimeout -> Maybe GrpcTimeout
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe GrpcTimeout
grpc
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpTimeout
http
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpTimeout
http2
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TcpTimeout
tcp

instance Data.ToJSON ListenerTimeout where
  toJSON :: ListenerTimeout -> Value
toJSON ListenerTimeout' {Maybe GrpcTimeout
Maybe HttpTimeout
Maybe TcpTimeout
tcp :: Maybe TcpTimeout
http2 :: Maybe HttpTimeout
http :: Maybe HttpTimeout
grpc :: Maybe GrpcTimeout
$sel:tcp:ListenerTimeout' :: ListenerTimeout -> Maybe TcpTimeout
$sel:http2:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
$sel:http:ListenerTimeout' :: ListenerTimeout -> Maybe HttpTimeout
$sel:grpc:ListenerTimeout' :: ListenerTimeout -> Maybe GrpcTimeout
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"grpc" 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 GrpcTimeout
grpc,
            (Key
"http" 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 HttpTimeout
http,
            (Key
"http2" 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 HttpTimeout
http2,
            (Key
"tcp" 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 TcpTimeout
tcp
          ]
      )