{-# 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.DeleteSnapshot
-- 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 snapshot. When you receive a successful response
-- from this operation, ElastiCache immediately begins deleting the
-- snapshot; you cannot cancel or revert this operation.
--
-- This operation is valid for Redis only.
module Amazonka.ElastiCache.DeleteSnapshot
  ( -- * Creating a Request
    DeleteSnapshot (..),
    newDeleteSnapshot,

    -- * Request Lenses
    deleteSnapshot_snapshotName,

    -- * Destructuring the Response
    DeleteSnapshotResponse (..),
    newDeleteSnapshotResponse,

    -- * Response Lenses
    deleteSnapshotResponse_snapshot,
    deleteSnapshotResponse_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 @DeleteSnapshot@ operation.
--
-- /See:/ 'newDeleteSnapshot' smart constructor.
data DeleteSnapshot = DeleteSnapshot'
  { -- | The name of the snapshot to be deleted.
    DeleteSnapshot -> Text
snapshotName :: Prelude.Text
  }
  deriving (DeleteSnapshot -> DeleteSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSnapshot -> DeleteSnapshot -> Bool
$c/= :: DeleteSnapshot -> DeleteSnapshot -> Bool
== :: DeleteSnapshot -> DeleteSnapshot -> Bool
$c== :: DeleteSnapshot -> DeleteSnapshot -> Bool
Prelude.Eq, ReadPrec [DeleteSnapshot]
ReadPrec DeleteSnapshot
Int -> ReadS DeleteSnapshot
ReadS [DeleteSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteSnapshot]
$creadListPrec :: ReadPrec [DeleteSnapshot]
readPrec :: ReadPrec DeleteSnapshot
$creadPrec :: ReadPrec DeleteSnapshot
readList :: ReadS [DeleteSnapshot]
$creadList :: ReadS [DeleteSnapshot]
readsPrec :: Int -> ReadS DeleteSnapshot
$creadsPrec :: Int -> ReadS DeleteSnapshot
Prelude.Read, Int -> DeleteSnapshot -> ShowS
[DeleteSnapshot] -> ShowS
DeleteSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSnapshot] -> ShowS
$cshowList :: [DeleteSnapshot] -> ShowS
show :: DeleteSnapshot -> String
$cshow :: DeleteSnapshot -> String
showsPrec :: Int -> DeleteSnapshot -> ShowS
$cshowsPrec :: Int -> DeleteSnapshot -> ShowS
Prelude.Show, forall x. Rep DeleteSnapshot x -> DeleteSnapshot
forall x. DeleteSnapshot -> Rep DeleteSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSnapshot x -> DeleteSnapshot
$cfrom :: forall x. DeleteSnapshot -> Rep DeleteSnapshot x
Prelude.Generic)

-- |
-- Create a value of 'DeleteSnapshot' 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:
--
-- 'snapshotName', 'deleteSnapshot_snapshotName' - The name of the snapshot to be deleted.
newDeleteSnapshot ::
  -- | 'snapshotName'
  Prelude.Text ->
  DeleteSnapshot
newDeleteSnapshot :: Text -> DeleteSnapshot
newDeleteSnapshot Text
pSnapshotName_ =
  DeleteSnapshot' {$sel:snapshotName:DeleteSnapshot' :: Text
snapshotName = Text
pSnapshotName_}

-- | The name of the snapshot to be deleted.
deleteSnapshot_snapshotName :: Lens.Lens' DeleteSnapshot Prelude.Text
deleteSnapshot_snapshotName :: Lens' DeleteSnapshot Text
deleteSnapshot_snapshotName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSnapshot' {Text
snapshotName :: Text
$sel:snapshotName:DeleteSnapshot' :: DeleteSnapshot -> Text
snapshotName} -> Text
snapshotName) (\s :: DeleteSnapshot
s@DeleteSnapshot' {} Text
a -> DeleteSnapshot
s {$sel:snapshotName:DeleteSnapshot' :: Text
snapshotName = Text
a} :: DeleteSnapshot)

instance Core.AWSRequest DeleteSnapshot where
  type
    AWSResponse DeleteSnapshot =
      DeleteSnapshotResponse
  request :: (Service -> Service) -> DeleteSnapshot -> Request DeleteSnapshot
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 DeleteSnapshot
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteSnapshot)))
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
"DeleteSnapshotResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Snapshot -> Int -> DeleteSnapshotResponse
DeleteSnapshotResponse'
            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
"Snapshot")
            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 DeleteSnapshot where
  hashWithSalt :: Int -> DeleteSnapshot -> Int
hashWithSalt Int
_salt DeleteSnapshot' {Text
snapshotName :: Text
$sel:snapshotName:DeleteSnapshot' :: DeleteSnapshot -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotName

instance Prelude.NFData DeleteSnapshot where
  rnf :: DeleteSnapshot -> ()
rnf DeleteSnapshot' {Text
snapshotName :: Text
$sel:snapshotName:DeleteSnapshot' :: DeleteSnapshot -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotName

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

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

instance Data.ToQuery DeleteSnapshot where
  toQuery :: DeleteSnapshot -> QueryString
toQuery DeleteSnapshot' {Text
snapshotName :: Text
$sel:snapshotName:DeleteSnapshot' :: DeleteSnapshot -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteSnapshot" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2015-02-02" :: Prelude.ByteString),
        ByteString
"SnapshotName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
snapshotName
      ]

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

-- |
-- Create a value of 'DeleteSnapshotResponse' 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:
--
-- 'snapshot', 'deleteSnapshotResponse_snapshot' - Undocumented member.
--
-- 'httpStatus', 'deleteSnapshotResponse_httpStatus' - The response's http status code.
newDeleteSnapshotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteSnapshotResponse
newDeleteSnapshotResponse :: Int -> DeleteSnapshotResponse
newDeleteSnapshotResponse Int
pHttpStatus_ =
  DeleteSnapshotResponse'
    { $sel:snapshot:DeleteSnapshotResponse' :: Maybe Snapshot
snapshot = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteSnapshotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
deleteSnapshotResponse_snapshot :: Lens.Lens' DeleteSnapshotResponse (Prelude.Maybe Snapshot)
deleteSnapshotResponse_snapshot :: Lens' DeleteSnapshotResponse (Maybe Snapshot)
deleteSnapshotResponse_snapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSnapshotResponse' {Maybe Snapshot
snapshot :: Maybe Snapshot
$sel:snapshot:DeleteSnapshotResponse' :: DeleteSnapshotResponse -> Maybe Snapshot
snapshot} -> Maybe Snapshot
snapshot) (\s :: DeleteSnapshotResponse
s@DeleteSnapshotResponse' {} Maybe Snapshot
a -> DeleteSnapshotResponse
s {$sel:snapshot:DeleteSnapshotResponse' :: Maybe Snapshot
snapshot = Maybe Snapshot
a} :: DeleteSnapshotResponse)

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

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