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

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

-- |
-- Create a value of 'HttpRoute' 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:
--
-- 'retryPolicy', 'httpRoute_retryPolicy' - An object that represents a retry policy.
--
-- 'timeout', 'httpRoute_timeout' - An object that represents types of timeouts.
--
-- 'action', 'httpRoute_action' - An object that represents the action to take if a match is determined.
--
-- 'match', 'httpRoute_match' - An object that represents the criteria for determining a request match.
newHttpRoute ::
  -- | 'action'
  HttpRouteAction ->
  -- | 'match'
  HttpRouteMatch ->
  HttpRoute
newHttpRoute :: HttpRouteAction -> HttpRouteMatch -> HttpRoute
newHttpRoute HttpRouteAction
pAction_ HttpRouteMatch
pMatch_ =
  HttpRoute'
    { $sel:retryPolicy:HttpRoute' :: Maybe HttpRetryPolicy
retryPolicy = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:HttpRoute' :: Maybe HttpTimeout
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:action:HttpRoute' :: HttpRouteAction
action = HttpRouteAction
pAction_,
      $sel:match:HttpRoute' :: HttpRouteMatch
match = HttpRouteMatch
pMatch_
    }

-- | An object that represents a retry policy.
httpRoute_retryPolicy :: Lens.Lens' HttpRoute (Prelude.Maybe HttpRetryPolicy)
httpRoute_retryPolicy :: Lens' HttpRoute (Maybe HttpRetryPolicy)
httpRoute_retryPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpRoute' {Maybe HttpRetryPolicy
retryPolicy :: Maybe HttpRetryPolicy
$sel:retryPolicy:HttpRoute' :: HttpRoute -> Maybe HttpRetryPolicy
retryPolicy} -> Maybe HttpRetryPolicy
retryPolicy) (\s :: HttpRoute
s@HttpRoute' {} Maybe HttpRetryPolicy
a -> HttpRoute
s {$sel:retryPolicy:HttpRoute' :: Maybe HttpRetryPolicy
retryPolicy = Maybe HttpRetryPolicy
a} :: HttpRoute)

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

-- | An object that represents the action to take if a match is determined.
httpRoute_action :: Lens.Lens' HttpRoute HttpRouteAction
httpRoute_action :: Lens' HttpRoute HttpRouteAction
httpRoute_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HttpRoute' {HttpRouteAction
action :: HttpRouteAction
$sel:action:HttpRoute' :: HttpRoute -> HttpRouteAction
action} -> HttpRouteAction
action) (\s :: HttpRoute
s@HttpRoute' {} HttpRouteAction
a -> HttpRoute
s {$sel:action:HttpRoute' :: HttpRouteAction
action = HttpRouteAction
a} :: HttpRoute)

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

instance Data.FromJSON HttpRoute where
  parseJSON :: Value -> Parser HttpRoute
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HttpRoute"
      ( \Object
x ->
          Maybe HttpRetryPolicy
-> Maybe HttpTimeout
-> HttpRouteAction
-> HttpRouteMatch
-> HttpRoute
HttpRoute'
            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
"retryPolicy")
            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")
            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
"match")
      )

instance Prelude.Hashable HttpRoute where
  hashWithSalt :: Int -> HttpRoute -> Int
hashWithSalt Int
_salt HttpRoute' {Maybe HttpTimeout
Maybe HttpRetryPolicy
HttpRouteMatch
HttpRouteAction
match :: HttpRouteMatch
action :: HttpRouteAction
timeout :: Maybe HttpTimeout
retryPolicy :: Maybe HttpRetryPolicy
$sel:match:HttpRoute' :: HttpRoute -> HttpRouteMatch
$sel:action:HttpRoute' :: HttpRoute -> HttpRouteAction
$sel:timeout:HttpRoute' :: HttpRoute -> Maybe HttpTimeout
$sel:retryPolicy:HttpRoute' :: HttpRoute -> Maybe HttpRetryPolicy
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpRetryPolicy
retryPolicy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpTimeout
timeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HttpRouteAction
action
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HttpRouteMatch
match

instance Prelude.NFData HttpRoute where
  rnf :: HttpRoute -> ()
rnf HttpRoute' {Maybe HttpTimeout
Maybe HttpRetryPolicy
HttpRouteMatch
HttpRouteAction
match :: HttpRouteMatch
action :: HttpRouteAction
timeout :: Maybe HttpTimeout
retryPolicy :: Maybe HttpRetryPolicy
$sel:match:HttpRoute' :: HttpRoute -> HttpRouteMatch
$sel:action:HttpRoute' :: HttpRoute -> HttpRouteAction
$sel:timeout:HttpRoute' :: HttpRoute -> Maybe HttpTimeout
$sel:retryPolicy:HttpRoute' :: HttpRoute -> Maybe HttpRetryPolicy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpRetryPolicy
retryPolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpTimeout
timeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HttpRouteAction
action
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HttpRouteMatch
match

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