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

import Amazonka.AppMesh.Types.TcpRouteAction
import Amazonka.AppMesh.Types.TcpRouteMatch
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 a TCP route type.
--
-- /See:/ 'newTcpRoute' smart constructor.
data TcpRoute = TcpRoute'
  { -- | An object that represents the criteria for determining a request match.
    TcpRoute -> Maybe TcpRouteMatch
match :: Prelude.Maybe TcpRouteMatch,
    -- | An object that represents types of timeouts.
    TcpRoute -> Maybe TcpTimeout
timeout :: Prelude.Maybe TcpTimeout,
    -- | The action to take if a match is determined.
    TcpRoute -> TcpRouteAction
action :: TcpRouteAction
  }
  deriving (TcpRoute -> TcpRoute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TcpRoute -> TcpRoute -> Bool
$c/= :: TcpRoute -> TcpRoute -> Bool
== :: TcpRoute -> TcpRoute -> Bool
$c== :: TcpRoute -> TcpRoute -> Bool
Prelude.Eq, ReadPrec [TcpRoute]
ReadPrec TcpRoute
Int -> ReadS TcpRoute
ReadS [TcpRoute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TcpRoute]
$creadListPrec :: ReadPrec [TcpRoute]
readPrec :: ReadPrec TcpRoute
$creadPrec :: ReadPrec TcpRoute
readList :: ReadS [TcpRoute]
$creadList :: ReadS [TcpRoute]
readsPrec :: Int -> ReadS TcpRoute
$creadsPrec :: Int -> ReadS TcpRoute
Prelude.Read, Int -> TcpRoute -> ShowS
[TcpRoute] -> ShowS
TcpRoute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TcpRoute] -> ShowS
$cshowList :: [TcpRoute] -> ShowS
show :: TcpRoute -> String
$cshow :: TcpRoute -> String
showsPrec :: Int -> TcpRoute -> ShowS
$cshowsPrec :: Int -> TcpRoute -> ShowS
Prelude.Show, forall x. Rep TcpRoute x -> TcpRoute
forall x. TcpRoute -> Rep TcpRoute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TcpRoute x -> TcpRoute
$cfrom :: forall x. TcpRoute -> Rep TcpRoute x
Prelude.Generic)

-- |
-- Create a value of 'TcpRoute' 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:
--
-- 'match', 'tcpRoute_match' - An object that represents the criteria for determining a request match.
--
-- 'timeout', 'tcpRoute_timeout' - An object that represents types of timeouts.
--
-- 'action', 'tcpRoute_action' - The action to take if a match is determined.
newTcpRoute ::
  -- | 'action'
  TcpRouteAction ->
  TcpRoute
newTcpRoute :: TcpRouteAction -> TcpRoute
newTcpRoute TcpRouteAction
pAction_ =
  TcpRoute'
    { $sel:match:TcpRoute' :: Maybe TcpRouteMatch
match = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:TcpRoute' :: Maybe TcpTimeout
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:action:TcpRoute' :: TcpRouteAction
action = TcpRouteAction
pAction_
    }

-- | An object that represents the criteria for determining a request match.
tcpRoute_match :: Lens.Lens' TcpRoute (Prelude.Maybe TcpRouteMatch)
tcpRoute_match :: Lens' TcpRoute (Maybe TcpRouteMatch)
tcpRoute_match = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TcpRoute' {Maybe TcpRouteMatch
match :: Maybe TcpRouteMatch
$sel:match:TcpRoute' :: TcpRoute -> Maybe TcpRouteMatch
match} -> Maybe TcpRouteMatch
match) (\s :: TcpRoute
s@TcpRoute' {} Maybe TcpRouteMatch
a -> TcpRoute
s {$sel:match:TcpRoute' :: Maybe TcpRouteMatch
match = Maybe TcpRouteMatch
a} :: TcpRoute)

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

-- | The action to take if a match is determined.
tcpRoute_action :: Lens.Lens' TcpRoute TcpRouteAction
tcpRoute_action :: Lens' TcpRoute TcpRouteAction
tcpRoute_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TcpRoute' {TcpRouteAction
action :: TcpRouteAction
$sel:action:TcpRoute' :: TcpRoute -> TcpRouteAction
action} -> TcpRouteAction
action) (\s :: TcpRoute
s@TcpRoute' {} TcpRouteAction
a -> TcpRoute
s {$sel:action:TcpRoute' :: TcpRouteAction
action = TcpRouteAction
a} :: TcpRoute)

instance Data.FromJSON TcpRoute where
  parseJSON :: Value -> Parser TcpRoute
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TcpRoute"
      ( \Object
x ->
          Maybe TcpRouteMatch
-> Maybe TcpTimeout -> TcpRouteAction -> TcpRoute
TcpRoute'
            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
"match")
            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 a
Data..: Key
"action")
      )

instance Prelude.Hashable TcpRoute where
  hashWithSalt :: Int -> TcpRoute -> Int
hashWithSalt Int
_salt TcpRoute' {Maybe TcpRouteMatch
Maybe TcpTimeout
TcpRouteAction
action :: TcpRouteAction
timeout :: Maybe TcpTimeout
match :: Maybe TcpRouteMatch
$sel:action:TcpRoute' :: TcpRoute -> TcpRouteAction
$sel:timeout:TcpRoute' :: TcpRoute -> Maybe TcpTimeout
$sel:match:TcpRoute' :: TcpRoute -> Maybe TcpRouteMatch
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TcpRouteMatch
match
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TcpTimeout
timeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TcpRouteAction
action

instance Prelude.NFData TcpRoute where
  rnf :: TcpRoute -> ()
rnf TcpRoute' {Maybe TcpRouteMatch
Maybe TcpTimeout
TcpRouteAction
action :: TcpRouteAction
timeout :: Maybe TcpTimeout
match :: Maybe TcpRouteMatch
$sel:action:TcpRoute' :: TcpRoute -> TcpRouteAction
$sel:timeout:TcpRoute' :: TcpRoute -> Maybe TcpTimeout
$sel:match:TcpRoute' :: TcpRoute -> Maybe TcpRouteMatch
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe TcpRouteMatch
match
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TcpTimeout
timeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TcpRouteAction
action

instance Data.ToJSON TcpRoute where
  toJSON :: TcpRoute -> Value
toJSON TcpRoute' {Maybe TcpRouteMatch
Maybe TcpTimeout
TcpRouteAction
action :: TcpRouteAction
timeout :: Maybe TcpTimeout
match :: Maybe TcpRouteMatch
$sel:action:TcpRoute' :: TcpRoute -> TcpRouteAction
$sel:timeout:TcpRoute' :: TcpRoute -> Maybe TcpTimeout
$sel:match:TcpRoute' :: TcpRoute -> Maybe TcpRouteMatch
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"match" 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 TcpRouteMatch
match,
            (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 TcpTimeout
timeout,
            forall a. a -> Maybe a
Prelude.Just (Key
"action" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TcpRouteAction
action)
          ]
      )