{-# 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.Route53RecoveryControlConfig.UpdateRoutingControl
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a routing control. You can only update the name of the routing
-- control. To get or update the routing control state, see the Recovery
-- Cluster (data plane) API actions for Amazon Route 53 Application
-- Recovery Controller.
module Amazonka.Route53RecoveryControlConfig.UpdateRoutingControl
  ( -- * Creating a Request
    UpdateRoutingControl (..),
    newUpdateRoutingControl,

    -- * Request Lenses
    updateRoutingControl_routingControlName,
    updateRoutingControl_routingControlArn,

    -- * Destructuring the Response
    UpdateRoutingControlResponse (..),
    newUpdateRoutingControlResponse,

    -- * Response Lenses
    updateRoutingControlResponse_routingControl,
    updateRoutingControlResponse_httpStatus,
  )
where

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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Route53RecoveryControlConfig.Types

-- | The details of the routing control that you\'re updating.
--
-- /See:/ 'newUpdateRoutingControl' smart constructor.
data UpdateRoutingControl = UpdateRoutingControl'
  { -- | The name of the routing control.
    UpdateRoutingControl -> Text
routingControlName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the routing control.
    UpdateRoutingControl -> Text
routingControlArn :: Prelude.Text
  }
  deriving (UpdateRoutingControl -> UpdateRoutingControl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRoutingControl -> UpdateRoutingControl -> Bool
$c/= :: UpdateRoutingControl -> UpdateRoutingControl -> Bool
== :: UpdateRoutingControl -> UpdateRoutingControl -> Bool
$c== :: UpdateRoutingControl -> UpdateRoutingControl -> Bool
Prelude.Eq, ReadPrec [UpdateRoutingControl]
ReadPrec UpdateRoutingControl
Int -> ReadS UpdateRoutingControl
ReadS [UpdateRoutingControl]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRoutingControl]
$creadListPrec :: ReadPrec [UpdateRoutingControl]
readPrec :: ReadPrec UpdateRoutingControl
$creadPrec :: ReadPrec UpdateRoutingControl
readList :: ReadS [UpdateRoutingControl]
$creadList :: ReadS [UpdateRoutingControl]
readsPrec :: Int -> ReadS UpdateRoutingControl
$creadsPrec :: Int -> ReadS UpdateRoutingControl
Prelude.Read, Int -> UpdateRoutingControl -> ShowS
[UpdateRoutingControl] -> ShowS
UpdateRoutingControl -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRoutingControl] -> ShowS
$cshowList :: [UpdateRoutingControl] -> ShowS
show :: UpdateRoutingControl -> String
$cshow :: UpdateRoutingControl -> String
showsPrec :: Int -> UpdateRoutingControl -> ShowS
$cshowsPrec :: Int -> UpdateRoutingControl -> ShowS
Prelude.Show, forall x. Rep UpdateRoutingControl x -> UpdateRoutingControl
forall x. UpdateRoutingControl -> Rep UpdateRoutingControl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRoutingControl x -> UpdateRoutingControl
$cfrom :: forall x. UpdateRoutingControl -> Rep UpdateRoutingControl x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRoutingControl' 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:
--
-- 'routingControlName', 'updateRoutingControl_routingControlName' - The name of the routing control.
--
-- 'routingControlArn', 'updateRoutingControl_routingControlArn' - The Amazon Resource Name (ARN) of the routing control.
newUpdateRoutingControl ::
  -- | 'routingControlName'
  Prelude.Text ->
  -- | 'routingControlArn'
  Prelude.Text ->
  UpdateRoutingControl
newUpdateRoutingControl :: Text -> Text -> UpdateRoutingControl
newUpdateRoutingControl
  Text
pRoutingControlName_
  Text
pRoutingControlArn_ =
    UpdateRoutingControl'
      { $sel:routingControlName:UpdateRoutingControl' :: Text
routingControlName =
          Text
pRoutingControlName_,
        $sel:routingControlArn:UpdateRoutingControl' :: Text
routingControlArn = Text
pRoutingControlArn_
      }

-- | The name of the routing control.
updateRoutingControl_routingControlName :: Lens.Lens' UpdateRoutingControl Prelude.Text
updateRoutingControl_routingControlName :: Lens' UpdateRoutingControl Text
updateRoutingControl_routingControlName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoutingControl' {Text
routingControlName :: Text
$sel:routingControlName:UpdateRoutingControl' :: UpdateRoutingControl -> Text
routingControlName} -> Text
routingControlName) (\s :: UpdateRoutingControl
s@UpdateRoutingControl' {} Text
a -> UpdateRoutingControl
s {$sel:routingControlName:UpdateRoutingControl' :: Text
routingControlName = Text
a} :: UpdateRoutingControl)

-- | The Amazon Resource Name (ARN) of the routing control.
updateRoutingControl_routingControlArn :: Lens.Lens' UpdateRoutingControl Prelude.Text
updateRoutingControl_routingControlArn :: Lens' UpdateRoutingControl Text
updateRoutingControl_routingControlArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoutingControl' {Text
routingControlArn :: Text
$sel:routingControlArn:UpdateRoutingControl' :: UpdateRoutingControl -> Text
routingControlArn} -> Text
routingControlArn) (\s :: UpdateRoutingControl
s@UpdateRoutingControl' {} Text
a -> UpdateRoutingControl
s {$sel:routingControlArn:UpdateRoutingControl' :: Text
routingControlArn = Text
a} :: UpdateRoutingControl)

instance Core.AWSRequest UpdateRoutingControl where
  type
    AWSResponse UpdateRoutingControl =
      UpdateRoutingControlResponse
  request :: (Service -> Service)
-> UpdateRoutingControl -> Request UpdateRoutingControl
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateRoutingControl
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateRoutingControl)))
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 RoutingControl -> Int -> UpdateRoutingControlResponse
UpdateRoutingControlResponse'
            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
"RoutingControl")
            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 UpdateRoutingControl where
  hashWithSalt :: Int -> UpdateRoutingControl -> Int
hashWithSalt Int
_salt UpdateRoutingControl' {Text
routingControlArn :: Text
routingControlName :: Text
$sel:routingControlArn:UpdateRoutingControl' :: UpdateRoutingControl -> Text
$sel:routingControlName:UpdateRoutingControl' :: UpdateRoutingControl -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routingControlName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routingControlArn

instance Prelude.NFData UpdateRoutingControl where
  rnf :: UpdateRoutingControl -> ()
rnf UpdateRoutingControl' {Text
routingControlArn :: Text
routingControlName :: Text
$sel:routingControlArn:UpdateRoutingControl' :: UpdateRoutingControl -> Text
$sel:routingControlName:UpdateRoutingControl' :: UpdateRoutingControl -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
routingControlName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
routingControlArn

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

instance Data.ToJSON UpdateRoutingControl where
  toJSON :: UpdateRoutingControl -> Value
toJSON UpdateRoutingControl' {Text
routingControlArn :: Text
routingControlName :: Text
$sel:routingControlArn:UpdateRoutingControl' :: UpdateRoutingControl -> Text
$sel:routingControlName:UpdateRoutingControl' :: UpdateRoutingControl -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"RoutingControlName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
routingControlName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"RoutingControlArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
routingControlArn)
          ]
      )

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

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

-- | /See:/ 'newUpdateRoutingControlResponse' smart constructor.
data UpdateRoutingControlResponse = UpdateRoutingControlResponse'
  { -- | The routing control that was updated.
    UpdateRoutingControlResponse -> Maybe RoutingControl
routingControl :: Prelude.Maybe RoutingControl,
    -- | The response's http status code.
    UpdateRoutingControlResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateRoutingControlResponse
-> UpdateRoutingControlResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRoutingControlResponse
-> UpdateRoutingControlResponse -> Bool
$c/= :: UpdateRoutingControlResponse
-> UpdateRoutingControlResponse -> Bool
== :: UpdateRoutingControlResponse
-> UpdateRoutingControlResponse -> Bool
$c== :: UpdateRoutingControlResponse
-> UpdateRoutingControlResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRoutingControlResponse]
ReadPrec UpdateRoutingControlResponse
Int -> ReadS UpdateRoutingControlResponse
ReadS [UpdateRoutingControlResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRoutingControlResponse]
$creadListPrec :: ReadPrec [UpdateRoutingControlResponse]
readPrec :: ReadPrec UpdateRoutingControlResponse
$creadPrec :: ReadPrec UpdateRoutingControlResponse
readList :: ReadS [UpdateRoutingControlResponse]
$creadList :: ReadS [UpdateRoutingControlResponse]
readsPrec :: Int -> ReadS UpdateRoutingControlResponse
$creadsPrec :: Int -> ReadS UpdateRoutingControlResponse
Prelude.Read, Int -> UpdateRoutingControlResponse -> ShowS
[UpdateRoutingControlResponse] -> ShowS
UpdateRoutingControlResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRoutingControlResponse] -> ShowS
$cshowList :: [UpdateRoutingControlResponse] -> ShowS
show :: UpdateRoutingControlResponse -> String
$cshow :: UpdateRoutingControlResponse -> String
showsPrec :: Int -> UpdateRoutingControlResponse -> ShowS
$cshowsPrec :: Int -> UpdateRoutingControlResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateRoutingControlResponse x -> UpdateRoutingControlResponse
forall x.
UpdateRoutingControlResponse -> Rep UpdateRoutingControlResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateRoutingControlResponse x -> UpdateRoutingControlResponse
$cfrom :: forall x.
UpdateRoutingControlResponse -> Rep UpdateRoutingControlResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRoutingControlResponse' 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:
--
-- 'routingControl', 'updateRoutingControlResponse_routingControl' - The routing control that was updated.
--
-- 'httpStatus', 'updateRoutingControlResponse_httpStatus' - The response's http status code.
newUpdateRoutingControlResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRoutingControlResponse
newUpdateRoutingControlResponse :: Int -> UpdateRoutingControlResponse
newUpdateRoutingControlResponse Int
pHttpStatus_ =
  UpdateRoutingControlResponse'
    { $sel:routingControl:UpdateRoutingControlResponse' :: Maybe RoutingControl
routingControl =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRoutingControlResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The routing control that was updated.
updateRoutingControlResponse_routingControl :: Lens.Lens' UpdateRoutingControlResponse (Prelude.Maybe RoutingControl)
updateRoutingControlResponse_routingControl :: Lens' UpdateRoutingControlResponse (Maybe RoutingControl)
updateRoutingControlResponse_routingControl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoutingControlResponse' {Maybe RoutingControl
routingControl :: Maybe RoutingControl
$sel:routingControl:UpdateRoutingControlResponse' :: UpdateRoutingControlResponse -> Maybe RoutingControl
routingControl} -> Maybe RoutingControl
routingControl) (\s :: UpdateRoutingControlResponse
s@UpdateRoutingControlResponse' {} Maybe RoutingControl
a -> UpdateRoutingControlResponse
s {$sel:routingControl:UpdateRoutingControlResponse' :: Maybe RoutingControl
routingControl = Maybe RoutingControl
a} :: UpdateRoutingControlResponse)

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

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