{-# 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.Route53RecoveryReadiness.UpdateRecoveryGroup
-- 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 recovery group.
module Amazonka.Route53RecoveryReadiness.UpdateRecoveryGroup
  ( -- * Creating a Request
    UpdateRecoveryGroup (..),
    newUpdateRecoveryGroup,

    -- * Request Lenses
    updateRecoveryGroup_recoveryGroupName,
    updateRecoveryGroup_cells,

    -- * Destructuring the Response
    UpdateRecoveryGroupResponse (..),
    newUpdateRecoveryGroupResponse,

    -- * Response Lenses
    updateRecoveryGroupResponse_cells,
    updateRecoveryGroupResponse_recoveryGroupArn,
    updateRecoveryGroupResponse_recoveryGroupName,
    updateRecoveryGroupResponse_tags,
    updateRecoveryGroupResponse_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.Route53RecoveryReadiness.Types

-- | Name of a recovery group.
--
-- /See:/ 'newUpdateRecoveryGroup' smart constructor.
data UpdateRecoveryGroup = UpdateRecoveryGroup'
  { -- | The name of a recovery group.
    UpdateRecoveryGroup -> Text
recoveryGroupName :: Prelude.Text,
    -- | A list of cell Amazon Resource Names (ARNs). This list completely
    -- replaces the previous list.
    UpdateRecoveryGroup -> [Text]
cells :: [Prelude.Text]
  }
  deriving (UpdateRecoveryGroup -> UpdateRecoveryGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRecoveryGroup -> UpdateRecoveryGroup -> Bool
$c/= :: UpdateRecoveryGroup -> UpdateRecoveryGroup -> Bool
== :: UpdateRecoveryGroup -> UpdateRecoveryGroup -> Bool
$c== :: UpdateRecoveryGroup -> UpdateRecoveryGroup -> Bool
Prelude.Eq, ReadPrec [UpdateRecoveryGroup]
ReadPrec UpdateRecoveryGroup
Int -> ReadS UpdateRecoveryGroup
ReadS [UpdateRecoveryGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRecoveryGroup]
$creadListPrec :: ReadPrec [UpdateRecoveryGroup]
readPrec :: ReadPrec UpdateRecoveryGroup
$creadPrec :: ReadPrec UpdateRecoveryGroup
readList :: ReadS [UpdateRecoveryGroup]
$creadList :: ReadS [UpdateRecoveryGroup]
readsPrec :: Int -> ReadS UpdateRecoveryGroup
$creadsPrec :: Int -> ReadS UpdateRecoveryGroup
Prelude.Read, Int -> UpdateRecoveryGroup -> ShowS
[UpdateRecoveryGroup] -> ShowS
UpdateRecoveryGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRecoveryGroup] -> ShowS
$cshowList :: [UpdateRecoveryGroup] -> ShowS
show :: UpdateRecoveryGroup -> String
$cshow :: UpdateRecoveryGroup -> String
showsPrec :: Int -> UpdateRecoveryGroup -> ShowS
$cshowsPrec :: Int -> UpdateRecoveryGroup -> ShowS
Prelude.Show, forall x. Rep UpdateRecoveryGroup x -> UpdateRecoveryGroup
forall x. UpdateRecoveryGroup -> Rep UpdateRecoveryGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRecoveryGroup x -> UpdateRecoveryGroup
$cfrom :: forall x. UpdateRecoveryGroup -> Rep UpdateRecoveryGroup x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRecoveryGroup' 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:
--
-- 'recoveryGroupName', 'updateRecoveryGroup_recoveryGroupName' - The name of a recovery group.
--
-- 'cells', 'updateRecoveryGroup_cells' - A list of cell Amazon Resource Names (ARNs). This list completely
-- replaces the previous list.
newUpdateRecoveryGroup ::
  -- | 'recoveryGroupName'
  Prelude.Text ->
  UpdateRecoveryGroup
newUpdateRecoveryGroup :: Text -> UpdateRecoveryGroup
newUpdateRecoveryGroup Text
pRecoveryGroupName_ =
  UpdateRecoveryGroup'
    { $sel:recoveryGroupName:UpdateRecoveryGroup' :: Text
recoveryGroupName =
        Text
pRecoveryGroupName_,
      $sel:cells:UpdateRecoveryGroup' :: [Text]
cells = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of a recovery group.
updateRecoveryGroup_recoveryGroupName :: Lens.Lens' UpdateRecoveryGroup Prelude.Text
updateRecoveryGroup_recoveryGroupName :: Lens' UpdateRecoveryGroup Text
updateRecoveryGroup_recoveryGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecoveryGroup' {Text
recoveryGroupName :: Text
$sel:recoveryGroupName:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> Text
recoveryGroupName} -> Text
recoveryGroupName) (\s :: UpdateRecoveryGroup
s@UpdateRecoveryGroup' {} Text
a -> UpdateRecoveryGroup
s {$sel:recoveryGroupName:UpdateRecoveryGroup' :: Text
recoveryGroupName = Text
a} :: UpdateRecoveryGroup)

-- | A list of cell Amazon Resource Names (ARNs). This list completely
-- replaces the previous list.
updateRecoveryGroup_cells :: Lens.Lens' UpdateRecoveryGroup [Prelude.Text]
updateRecoveryGroup_cells :: Lens' UpdateRecoveryGroup [Text]
updateRecoveryGroup_cells = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecoveryGroup' {[Text]
cells :: [Text]
$sel:cells:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> [Text]
cells} -> [Text]
cells) (\s :: UpdateRecoveryGroup
s@UpdateRecoveryGroup' {} [Text]
a -> UpdateRecoveryGroup
s {$sel:cells:UpdateRecoveryGroup' :: [Text]
cells = [Text]
a} :: UpdateRecoveryGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest UpdateRecoveryGroup where
  type
    AWSResponse UpdateRecoveryGroup =
      UpdateRecoveryGroupResponse
  request :: (Service -> Service)
-> UpdateRecoveryGroup -> Request UpdateRecoveryGroup
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 UpdateRecoveryGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateRecoveryGroup)))
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 [Text]
-> Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Int
-> UpdateRecoveryGroupResponse
UpdateRecoveryGroupResponse'
            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
"cells" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"recoveryGroupArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"recoveryGroupName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 UpdateRecoveryGroup where
  hashWithSalt :: Int -> UpdateRecoveryGroup -> Int
hashWithSalt Int
_salt UpdateRecoveryGroup' {[Text]
Text
cells :: [Text]
recoveryGroupName :: Text
$sel:cells:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> [Text]
$sel:recoveryGroupName:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
recoveryGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
cells

instance Prelude.NFData UpdateRecoveryGroup where
  rnf :: UpdateRecoveryGroup -> ()
rnf UpdateRecoveryGroup' {[Text]
Text
cells :: [Text]
recoveryGroupName :: Text
$sel:cells:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> [Text]
$sel:recoveryGroupName:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
recoveryGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
cells

instance Data.ToHeaders UpdateRecoveryGroup where
  toHeaders :: UpdateRecoveryGroup -> 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 UpdateRecoveryGroup where
  toJSON :: UpdateRecoveryGroup -> Value
toJSON UpdateRecoveryGroup' {[Text]
Text
cells :: [Text]
recoveryGroupName :: Text
$sel:cells:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> [Text]
$sel:recoveryGroupName:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"cells" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
cells)]
      )

instance Data.ToPath UpdateRecoveryGroup where
  toPath :: UpdateRecoveryGroup -> ByteString
toPath UpdateRecoveryGroup' {[Text]
Text
cells :: [Text]
recoveryGroupName :: Text
$sel:cells:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> [Text]
$sel:recoveryGroupName:UpdateRecoveryGroup' :: UpdateRecoveryGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/recoverygroups/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
recoveryGroupName]

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

-- | /See:/ 'newUpdateRecoveryGroupResponse' smart constructor.
data UpdateRecoveryGroupResponse = UpdateRecoveryGroupResponse'
  { -- | A list of a cell\'s Amazon Resource Names (ARNs).
    UpdateRecoveryGroupResponse -> Maybe [Text]
cells :: Prelude.Maybe [Prelude.Text],
    -- | The Amazon Resource Name (ARN) for the recovery group.
    UpdateRecoveryGroupResponse -> Maybe Text
recoveryGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the recovery group.
    UpdateRecoveryGroupResponse -> Maybe Text
recoveryGroupName :: Prelude.Maybe Prelude.Text,
    -- | The tags associated with the recovery group.
    UpdateRecoveryGroupResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    UpdateRecoveryGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateRecoveryGroupResponse -> UpdateRecoveryGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRecoveryGroupResponse -> UpdateRecoveryGroupResponse -> Bool
$c/= :: UpdateRecoveryGroupResponse -> UpdateRecoveryGroupResponse -> Bool
== :: UpdateRecoveryGroupResponse -> UpdateRecoveryGroupResponse -> Bool
$c== :: UpdateRecoveryGroupResponse -> UpdateRecoveryGroupResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRecoveryGroupResponse]
ReadPrec UpdateRecoveryGroupResponse
Int -> ReadS UpdateRecoveryGroupResponse
ReadS [UpdateRecoveryGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRecoveryGroupResponse]
$creadListPrec :: ReadPrec [UpdateRecoveryGroupResponse]
readPrec :: ReadPrec UpdateRecoveryGroupResponse
$creadPrec :: ReadPrec UpdateRecoveryGroupResponse
readList :: ReadS [UpdateRecoveryGroupResponse]
$creadList :: ReadS [UpdateRecoveryGroupResponse]
readsPrec :: Int -> ReadS UpdateRecoveryGroupResponse
$creadsPrec :: Int -> ReadS UpdateRecoveryGroupResponse
Prelude.Read, Int -> UpdateRecoveryGroupResponse -> ShowS
[UpdateRecoveryGroupResponse] -> ShowS
UpdateRecoveryGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRecoveryGroupResponse] -> ShowS
$cshowList :: [UpdateRecoveryGroupResponse] -> ShowS
show :: UpdateRecoveryGroupResponse -> String
$cshow :: UpdateRecoveryGroupResponse -> String
showsPrec :: Int -> UpdateRecoveryGroupResponse -> ShowS
$cshowsPrec :: Int -> UpdateRecoveryGroupResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateRecoveryGroupResponse x -> UpdateRecoveryGroupResponse
forall x.
UpdateRecoveryGroupResponse -> Rep UpdateRecoveryGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateRecoveryGroupResponse x -> UpdateRecoveryGroupResponse
$cfrom :: forall x.
UpdateRecoveryGroupResponse -> Rep UpdateRecoveryGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRecoveryGroupResponse' 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:
--
-- 'cells', 'updateRecoveryGroupResponse_cells' - A list of a cell\'s Amazon Resource Names (ARNs).
--
-- 'recoveryGroupArn', 'updateRecoveryGroupResponse_recoveryGroupArn' - The Amazon Resource Name (ARN) for the recovery group.
--
-- 'recoveryGroupName', 'updateRecoveryGroupResponse_recoveryGroupName' - The name of the recovery group.
--
-- 'tags', 'updateRecoveryGroupResponse_tags' - The tags associated with the recovery group.
--
-- 'httpStatus', 'updateRecoveryGroupResponse_httpStatus' - The response's http status code.
newUpdateRecoveryGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRecoveryGroupResponse
newUpdateRecoveryGroupResponse :: Int -> UpdateRecoveryGroupResponse
newUpdateRecoveryGroupResponse Int
pHttpStatus_ =
  UpdateRecoveryGroupResponse'
    { $sel:cells:UpdateRecoveryGroupResponse' :: Maybe [Text]
cells =
        forall a. Maybe a
Prelude.Nothing,
      $sel:recoveryGroupArn:UpdateRecoveryGroupResponse' :: Maybe Text
recoveryGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:recoveryGroupName:UpdateRecoveryGroupResponse' :: Maybe Text
recoveryGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:UpdateRecoveryGroupResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRecoveryGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of a cell\'s Amazon Resource Names (ARNs).
updateRecoveryGroupResponse_cells :: Lens.Lens' UpdateRecoveryGroupResponse (Prelude.Maybe [Prelude.Text])
updateRecoveryGroupResponse_cells :: Lens' UpdateRecoveryGroupResponse (Maybe [Text])
updateRecoveryGroupResponse_cells = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecoveryGroupResponse' {Maybe [Text]
cells :: Maybe [Text]
$sel:cells:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe [Text]
cells} -> Maybe [Text]
cells) (\s :: UpdateRecoveryGroupResponse
s@UpdateRecoveryGroupResponse' {} Maybe [Text]
a -> UpdateRecoveryGroupResponse
s {$sel:cells:UpdateRecoveryGroupResponse' :: Maybe [Text]
cells = Maybe [Text]
a} :: UpdateRecoveryGroupResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The Amazon Resource Name (ARN) for the recovery group.
updateRecoveryGroupResponse_recoveryGroupArn :: Lens.Lens' UpdateRecoveryGroupResponse (Prelude.Maybe Prelude.Text)
updateRecoveryGroupResponse_recoveryGroupArn :: Lens' UpdateRecoveryGroupResponse (Maybe Text)
updateRecoveryGroupResponse_recoveryGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecoveryGroupResponse' {Maybe Text
recoveryGroupArn :: Maybe Text
$sel:recoveryGroupArn:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe Text
recoveryGroupArn} -> Maybe Text
recoveryGroupArn) (\s :: UpdateRecoveryGroupResponse
s@UpdateRecoveryGroupResponse' {} Maybe Text
a -> UpdateRecoveryGroupResponse
s {$sel:recoveryGroupArn:UpdateRecoveryGroupResponse' :: Maybe Text
recoveryGroupArn = Maybe Text
a} :: UpdateRecoveryGroupResponse)

-- | The name of the recovery group.
updateRecoveryGroupResponse_recoveryGroupName :: Lens.Lens' UpdateRecoveryGroupResponse (Prelude.Maybe Prelude.Text)
updateRecoveryGroupResponse_recoveryGroupName :: Lens' UpdateRecoveryGroupResponse (Maybe Text)
updateRecoveryGroupResponse_recoveryGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecoveryGroupResponse' {Maybe Text
recoveryGroupName :: Maybe Text
$sel:recoveryGroupName:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe Text
recoveryGroupName} -> Maybe Text
recoveryGroupName) (\s :: UpdateRecoveryGroupResponse
s@UpdateRecoveryGroupResponse' {} Maybe Text
a -> UpdateRecoveryGroupResponse
s {$sel:recoveryGroupName:UpdateRecoveryGroupResponse' :: Maybe Text
recoveryGroupName = Maybe Text
a} :: UpdateRecoveryGroupResponse)

-- | The tags associated with the recovery group.
updateRecoveryGroupResponse_tags :: Lens.Lens' UpdateRecoveryGroupResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateRecoveryGroupResponse_tags :: Lens' UpdateRecoveryGroupResponse (Maybe (HashMap Text Text))
updateRecoveryGroupResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecoveryGroupResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: UpdateRecoveryGroupResponse
s@UpdateRecoveryGroupResponse' {} Maybe (HashMap Text Text)
a -> UpdateRecoveryGroupResponse
s {$sel:tags:UpdateRecoveryGroupResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: UpdateRecoveryGroupResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData UpdateRecoveryGroupResponse where
  rnf :: UpdateRecoveryGroupResponse -> ()
rnf UpdateRecoveryGroupResponse' {Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
recoveryGroupName :: Maybe Text
recoveryGroupArn :: Maybe Text
cells :: Maybe [Text]
$sel:httpStatus:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Int
$sel:tags:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe (HashMap Text Text)
$sel:recoveryGroupName:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe Text
$sel:recoveryGroupArn:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe Text
$sel:cells:UpdateRecoveryGroupResponse' :: UpdateRecoveryGroupResponse -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
cells
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recoveryGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recoveryGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus