{-# 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.ElastiCache.DeleteReplicationGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes an existing replication group. By default, this operation
-- deletes the entire replication group, including the primary\/primaries
-- and all of the read replicas. If the replication group has only one
-- primary, you can optionally delete only the read replicas, while
-- retaining the primary by setting @RetainPrimaryCluster=true@.
--
-- When you receive a successful response from this operation, Amazon
-- ElastiCache immediately begins deleting the selected resources; you
-- cannot cancel or revert this operation.
--
-- This operation is valid for Redis only.
module Amazonka.ElastiCache.DeleteReplicationGroup
  ( -- * Creating a Request
    DeleteReplicationGroup (..),
    newDeleteReplicationGroup,

    -- * Request Lenses
    deleteReplicationGroup_finalSnapshotIdentifier,
    deleteReplicationGroup_retainPrimaryCluster,
    deleteReplicationGroup_replicationGroupId,

    -- * Destructuring the Response
    DeleteReplicationGroupResponse (..),
    newDeleteReplicationGroupResponse,

    -- * Response Lenses
    deleteReplicationGroupResponse_replicationGroup,
    deleteReplicationGroupResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElastiCache.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Represents the input of a @DeleteReplicationGroup@ operation.
--
-- /See:/ 'newDeleteReplicationGroup' smart constructor.
data DeleteReplicationGroup = DeleteReplicationGroup'
  { -- | The name of a final node group (shard) snapshot. ElastiCache creates the
    -- snapshot from the primary node in the cluster, rather than one of the
    -- replicas; this is to ensure that it captures the freshest data. After
    -- the final snapshot is taken, the replication group is immediately
    -- deleted.
    DeleteReplicationGroup -> Maybe Text
finalSnapshotIdentifier :: Prelude.Maybe Prelude.Text,
    -- | If set to @true@, all of the read replicas are deleted, but the primary
    -- node is retained.
    DeleteReplicationGroup -> Maybe Bool
retainPrimaryCluster :: Prelude.Maybe Prelude.Bool,
    -- | The identifier for the cluster to be deleted. This parameter is not case
    -- sensitive.
    DeleteReplicationGroup -> Text
replicationGroupId :: Prelude.Text
  }
  deriving (DeleteReplicationGroup -> DeleteReplicationGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteReplicationGroup -> DeleteReplicationGroup -> Bool
$c/= :: DeleteReplicationGroup -> DeleteReplicationGroup -> Bool
== :: DeleteReplicationGroup -> DeleteReplicationGroup -> Bool
$c== :: DeleteReplicationGroup -> DeleteReplicationGroup -> Bool
Prelude.Eq, ReadPrec [DeleteReplicationGroup]
ReadPrec DeleteReplicationGroup
Int -> ReadS DeleteReplicationGroup
ReadS [DeleteReplicationGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteReplicationGroup]
$creadListPrec :: ReadPrec [DeleteReplicationGroup]
readPrec :: ReadPrec DeleteReplicationGroup
$creadPrec :: ReadPrec DeleteReplicationGroup
readList :: ReadS [DeleteReplicationGroup]
$creadList :: ReadS [DeleteReplicationGroup]
readsPrec :: Int -> ReadS DeleteReplicationGroup
$creadsPrec :: Int -> ReadS DeleteReplicationGroup
Prelude.Read, Int -> DeleteReplicationGroup -> ShowS
[DeleteReplicationGroup] -> ShowS
DeleteReplicationGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteReplicationGroup] -> ShowS
$cshowList :: [DeleteReplicationGroup] -> ShowS
show :: DeleteReplicationGroup -> String
$cshow :: DeleteReplicationGroup -> String
showsPrec :: Int -> DeleteReplicationGroup -> ShowS
$cshowsPrec :: Int -> DeleteReplicationGroup -> ShowS
Prelude.Show, forall x. Rep DeleteReplicationGroup x -> DeleteReplicationGroup
forall x. DeleteReplicationGroup -> Rep DeleteReplicationGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteReplicationGroup x -> DeleteReplicationGroup
$cfrom :: forall x. DeleteReplicationGroup -> Rep DeleteReplicationGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteReplicationGroup' 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:
--
-- 'finalSnapshotIdentifier', 'deleteReplicationGroup_finalSnapshotIdentifier' - The name of a final node group (shard) snapshot. ElastiCache creates the
-- snapshot from the primary node in the cluster, rather than one of the
-- replicas; this is to ensure that it captures the freshest data. After
-- the final snapshot is taken, the replication group is immediately
-- deleted.
--
-- 'retainPrimaryCluster', 'deleteReplicationGroup_retainPrimaryCluster' - If set to @true@, all of the read replicas are deleted, but the primary
-- node is retained.
--
-- 'replicationGroupId', 'deleteReplicationGroup_replicationGroupId' - The identifier for the cluster to be deleted. This parameter is not case
-- sensitive.
newDeleteReplicationGroup ::
  -- | 'replicationGroupId'
  Prelude.Text ->
  DeleteReplicationGroup
newDeleteReplicationGroup :: Text -> DeleteReplicationGroup
newDeleteReplicationGroup Text
pReplicationGroupId_ =
  DeleteReplicationGroup'
    { $sel:finalSnapshotIdentifier:DeleteReplicationGroup' :: Maybe Text
finalSnapshotIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:retainPrimaryCluster:DeleteReplicationGroup' :: Maybe Bool
retainPrimaryCluster = forall a. Maybe a
Prelude.Nothing,
      $sel:replicationGroupId:DeleteReplicationGroup' :: Text
replicationGroupId = Text
pReplicationGroupId_
    }

-- | The name of a final node group (shard) snapshot. ElastiCache creates the
-- snapshot from the primary node in the cluster, rather than one of the
-- replicas; this is to ensure that it captures the freshest data. After
-- the final snapshot is taken, the replication group is immediately
-- deleted.
deleteReplicationGroup_finalSnapshotIdentifier :: Lens.Lens' DeleteReplicationGroup (Prelude.Maybe Prelude.Text)
deleteReplicationGroup_finalSnapshotIdentifier :: Lens' DeleteReplicationGroup (Maybe Text)
deleteReplicationGroup_finalSnapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteReplicationGroup' {Maybe Text
finalSnapshotIdentifier :: Maybe Text
$sel:finalSnapshotIdentifier:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Text
finalSnapshotIdentifier} -> Maybe Text
finalSnapshotIdentifier) (\s :: DeleteReplicationGroup
s@DeleteReplicationGroup' {} Maybe Text
a -> DeleteReplicationGroup
s {$sel:finalSnapshotIdentifier:DeleteReplicationGroup' :: Maybe Text
finalSnapshotIdentifier = Maybe Text
a} :: DeleteReplicationGroup)

-- | If set to @true@, all of the read replicas are deleted, but the primary
-- node is retained.
deleteReplicationGroup_retainPrimaryCluster :: Lens.Lens' DeleteReplicationGroup (Prelude.Maybe Prelude.Bool)
deleteReplicationGroup_retainPrimaryCluster :: Lens' DeleteReplicationGroup (Maybe Bool)
deleteReplicationGroup_retainPrimaryCluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteReplicationGroup' {Maybe Bool
retainPrimaryCluster :: Maybe Bool
$sel:retainPrimaryCluster:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Bool
retainPrimaryCluster} -> Maybe Bool
retainPrimaryCluster) (\s :: DeleteReplicationGroup
s@DeleteReplicationGroup' {} Maybe Bool
a -> DeleteReplicationGroup
s {$sel:retainPrimaryCluster:DeleteReplicationGroup' :: Maybe Bool
retainPrimaryCluster = Maybe Bool
a} :: DeleteReplicationGroup)

-- | The identifier for the cluster to be deleted. This parameter is not case
-- sensitive.
deleteReplicationGroup_replicationGroupId :: Lens.Lens' DeleteReplicationGroup Prelude.Text
deleteReplicationGroup_replicationGroupId :: Lens' DeleteReplicationGroup Text
deleteReplicationGroup_replicationGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteReplicationGroup' {Text
replicationGroupId :: Text
$sel:replicationGroupId:DeleteReplicationGroup' :: DeleteReplicationGroup -> Text
replicationGroupId} -> Text
replicationGroupId) (\s :: DeleteReplicationGroup
s@DeleteReplicationGroup' {} Text
a -> DeleteReplicationGroup
s {$sel:replicationGroupId:DeleteReplicationGroup' :: Text
replicationGroupId = Text
a} :: DeleteReplicationGroup)

instance Core.AWSRequest DeleteReplicationGroup where
  type
    AWSResponse DeleteReplicationGroup =
      DeleteReplicationGroupResponse
  request :: (Service -> Service)
-> DeleteReplicationGroup -> Request DeleteReplicationGroup
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteReplicationGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteReplicationGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DeleteReplicationGroupResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ReplicationGroup -> Int -> DeleteReplicationGroupResponse
DeleteReplicationGroupResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ReplicationGroup")
            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 DeleteReplicationGroup where
  hashWithSalt :: Int -> DeleteReplicationGroup -> Int
hashWithSalt Int
_salt DeleteReplicationGroup' {Maybe Bool
Maybe Text
Text
replicationGroupId :: Text
retainPrimaryCluster :: Maybe Bool
finalSnapshotIdentifier :: Maybe Text
$sel:replicationGroupId:DeleteReplicationGroup' :: DeleteReplicationGroup -> Text
$sel:retainPrimaryCluster:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Bool
$sel:finalSnapshotIdentifier:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
finalSnapshotIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
retainPrimaryCluster
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
replicationGroupId

instance Prelude.NFData DeleteReplicationGroup where
  rnf :: DeleteReplicationGroup -> ()
rnf DeleteReplicationGroup' {Maybe Bool
Maybe Text
Text
replicationGroupId :: Text
retainPrimaryCluster :: Maybe Bool
finalSnapshotIdentifier :: Maybe Text
$sel:replicationGroupId:DeleteReplicationGroup' :: DeleteReplicationGroup -> Text
$sel:retainPrimaryCluster:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Bool
$sel:finalSnapshotIdentifier:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
finalSnapshotIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
retainPrimaryCluster
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
replicationGroupId

instance Data.ToHeaders DeleteReplicationGroup where
  toHeaders :: DeleteReplicationGroup -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DeleteReplicationGroup where
  toQuery :: DeleteReplicationGroup -> QueryString
toQuery DeleteReplicationGroup' {Maybe Bool
Maybe Text
Text
replicationGroupId :: Text
retainPrimaryCluster :: Maybe Bool
finalSnapshotIdentifier :: Maybe Text
$sel:replicationGroupId:DeleteReplicationGroup' :: DeleteReplicationGroup -> Text
$sel:retainPrimaryCluster:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Bool
$sel:finalSnapshotIdentifier:DeleteReplicationGroup' :: DeleteReplicationGroup -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteReplicationGroup" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2015-02-02" :: Prelude.ByteString),
        ByteString
"FinalSnapshotIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
finalSnapshotIdentifier,
        ByteString
"RetainPrimaryCluster" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
retainPrimaryCluster,
        ByteString
"ReplicationGroupId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
replicationGroupId
      ]

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

-- |
-- Create a value of 'DeleteReplicationGroupResponse' 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:
--
-- 'replicationGroup', 'deleteReplicationGroupResponse_replicationGroup' - Undocumented member.
--
-- 'httpStatus', 'deleteReplicationGroupResponse_httpStatus' - The response's http status code.
newDeleteReplicationGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteReplicationGroupResponse
newDeleteReplicationGroupResponse :: Int -> DeleteReplicationGroupResponse
newDeleteReplicationGroupResponse Int
pHttpStatus_ =
  DeleteReplicationGroupResponse'
    { $sel:replicationGroup:DeleteReplicationGroupResponse' :: Maybe ReplicationGroup
replicationGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteReplicationGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
deleteReplicationGroupResponse_replicationGroup :: Lens.Lens' DeleteReplicationGroupResponse (Prelude.Maybe ReplicationGroup)
deleteReplicationGroupResponse_replicationGroup :: Lens' DeleteReplicationGroupResponse (Maybe ReplicationGroup)
deleteReplicationGroupResponse_replicationGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteReplicationGroupResponse' {Maybe ReplicationGroup
replicationGroup :: Maybe ReplicationGroup
$sel:replicationGroup:DeleteReplicationGroupResponse' :: DeleteReplicationGroupResponse -> Maybe ReplicationGroup
replicationGroup} -> Maybe ReplicationGroup
replicationGroup) (\s :: DeleteReplicationGroupResponse
s@DeleteReplicationGroupResponse' {} Maybe ReplicationGroup
a -> DeleteReplicationGroupResponse
s {$sel:replicationGroup:DeleteReplicationGroupResponse' :: Maybe ReplicationGroup
replicationGroup = Maybe ReplicationGroup
a} :: DeleteReplicationGroupResponse)

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

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