{-# 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.FSx.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 Amazon FSx for OpenZFS snapshot. After deletion, the snapshot
-- no longer exists, and its data is gone. Deleting a snapshot doesn\'t
-- affect snapshots stored in a file system backup.
--
-- The @DeleteSnapshot@ operation returns instantly. The snapshot appears
-- with the lifecycle status of @DELETING@ until the deletion is complete.
module Amazonka.FSx.DeleteSnapshot
  ( -- * Creating a Request
    DeleteSnapshot (..),
    newDeleteSnapshot,

    -- * Request Lenses
    deleteSnapshot_clientRequestToken,
    deleteSnapshot_snapshotId,

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

    -- * Response Lenses
    deleteSnapshotResponse_lifecycle,
    deleteSnapshotResponse_snapshotId,
    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.FSx.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteSnapshot' smart constructor.
data DeleteSnapshot = DeleteSnapshot'
  { DeleteSnapshot -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the snapshot that you want to delete.
    DeleteSnapshot -> Text
snapshotId :: 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:
--
-- 'clientRequestToken', 'deleteSnapshot_clientRequestToken' - Undocumented member.
--
-- 'snapshotId', 'deleteSnapshot_snapshotId' - The ID of the snapshot that you want to delete.
newDeleteSnapshot ::
  -- | 'snapshotId'
  Prelude.Text ->
  DeleteSnapshot
newDeleteSnapshot :: Text -> DeleteSnapshot
newDeleteSnapshot Text
pSnapshotId_ =
  DeleteSnapshot'
    { $sel:clientRequestToken:DeleteSnapshot' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotId:DeleteSnapshot' :: Text
snapshotId = Text
pSnapshotId_
    }

-- | Undocumented member.
deleteSnapshot_clientRequestToken :: Lens.Lens' DeleteSnapshot (Prelude.Maybe Prelude.Text)
deleteSnapshot_clientRequestToken :: Lens' DeleteSnapshot (Maybe Text)
deleteSnapshot_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSnapshot' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:DeleteSnapshot' :: DeleteSnapshot -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: DeleteSnapshot
s@DeleteSnapshot' {} Maybe Text
a -> DeleteSnapshot
s {$sel:clientRequestToken:DeleteSnapshot' :: Maybe Text
clientRequestToken = Maybe Text
a} :: DeleteSnapshot)

-- | The ID of the snapshot that you want to delete.
deleteSnapshot_snapshotId :: Lens.Lens' DeleteSnapshot Prelude.Text
deleteSnapshot_snapshotId :: Lens' DeleteSnapshot Text
deleteSnapshot_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSnapshot' {Text
snapshotId :: Text
$sel:snapshotId:DeleteSnapshot' :: DeleteSnapshot -> Text
snapshotId} -> Text
snapshotId) (\s :: DeleteSnapshot
s@DeleteSnapshot' {} Text
a -> DeleteSnapshot
s {$sel:snapshotId:DeleteSnapshot' :: Text
snapshotId = 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, ToJSON a) => Service -> a -> Request a
Request.postJSON (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 =>
(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 SnapshotLifecycle
-> Maybe Text -> Int -> DeleteSnapshotResponse
DeleteSnapshotResponse'
            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
"Lifecycle")
            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
"SnapshotId")
            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' {Maybe Text
Text
snapshotId :: Text
clientRequestToken :: Maybe Text
$sel:snapshotId:DeleteSnapshot' :: DeleteSnapshot -> Text
$sel:clientRequestToken:DeleteSnapshot' :: DeleteSnapshot -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotId

instance Prelude.NFData DeleteSnapshot where
  rnf :: DeleteSnapshot -> ()
rnf DeleteSnapshot' {Maybe Text
Text
snapshotId :: Text
clientRequestToken :: Maybe Text
$sel:snapshotId:DeleteSnapshot' :: DeleteSnapshot -> Text
$sel:clientRequestToken:DeleteSnapshot' :: DeleteSnapshot -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotId

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

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

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 = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDeleteSnapshotResponse' smart constructor.
data DeleteSnapshotResponse = DeleteSnapshotResponse'
  { -- | The lifecycle status of the snapshot. If the @DeleteSnapshot@ operation
    -- is successful, this status is @DELETING@.
    DeleteSnapshotResponse -> Maybe SnapshotLifecycle
lifecycle :: Prelude.Maybe SnapshotLifecycle,
    -- | The ID of the deleted snapshot.
    DeleteSnapshotResponse -> Maybe Text
snapshotId :: Prelude.Maybe Prelude.Text,
    -- | 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:
--
-- 'lifecycle', 'deleteSnapshotResponse_lifecycle' - The lifecycle status of the snapshot. If the @DeleteSnapshot@ operation
-- is successful, this status is @DELETING@.
--
-- 'snapshotId', 'deleteSnapshotResponse_snapshotId' - The ID of the deleted snapshot.
--
-- 'httpStatus', 'deleteSnapshotResponse_httpStatus' - The response's http status code.
newDeleteSnapshotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteSnapshotResponse
newDeleteSnapshotResponse :: Int -> DeleteSnapshotResponse
newDeleteSnapshotResponse Int
pHttpStatus_ =
  DeleteSnapshotResponse'
    { $sel:lifecycle:DeleteSnapshotResponse' :: Maybe SnapshotLifecycle
lifecycle =
        forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotId:DeleteSnapshotResponse' :: Maybe Text
snapshotId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteSnapshotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The lifecycle status of the snapshot. If the @DeleteSnapshot@ operation
-- is successful, this status is @DELETING@.
deleteSnapshotResponse_lifecycle :: Lens.Lens' DeleteSnapshotResponse (Prelude.Maybe SnapshotLifecycle)
deleteSnapshotResponse_lifecycle :: Lens' DeleteSnapshotResponse (Maybe SnapshotLifecycle)
deleteSnapshotResponse_lifecycle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSnapshotResponse' {Maybe SnapshotLifecycle
lifecycle :: Maybe SnapshotLifecycle
$sel:lifecycle:DeleteSnapshotResponse' :: DeleteSnapshotResponse -> Maybe SnapshotLifecycle
lifecycle} -> Maybe SnapshotLifecycle
lifecycle) (\s :: DeleteSnapshotResponse
s@DeleteSnapshotResponse' {} Maybe SnapshotLifecycle
a -> DeleteSnapshotResponse
s {$sel:lifecycle:DeleteSnapshotResponse' :: Maybe SnapshotLifecycle
lifecycle = Maybe SnapshotLifecycle
a} :: DeleteSnapshotResponse)

-- | The ID of the deleted snapshot.
deleteSnapshotResponse_snapshotId :: Lens.Lens' DeleteSnapshotResponse (Prelude.Maybe Prelude.Text)
deleteSnapshotResponse_snapshotId :: Lens' DeleteSnapshotResponse (Maybe Text)
deleteSnapshotResponse_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSnapshotResponse' {Maybe Text
snapshotId :: Maybe Text
$sel:snapshotId:DeleteSnapshotResponse' :: DeleteSnapshotResponse -> Maybe Text
snapshotId} -> Maybe Text
snapshotId) (\s :: DeleteSnapshotResponse
s@DeleteSnapshotResponse' {} Maybe Text
a -> DeleteSnapshotResponse
s {$sel:snapshotId:DeleteSnapshotResponse' :: Maybe Text
snapshotId = Maybe Text
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 Text
Maybe SnapshotLifecycle
httpStatus :: Int
snapshotId :: Maybe Text
lifecycle :: Maybe SnapshotLifecycle
$sel:httpStatus:DeleteSnapshotResponse' :: DeleteSnapshotResponse -> Int
$sel:snapshotId:DeleteSnapshotResponse' :: DeleteSnapshotResponse -> Maybe Text
$sel:lifecycle:DeleteSnapshotResponse' :: DeleteSnapshotResponse -> Maybe SnapshotLifecycle
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SnapshotLifecycle
lifecycle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snapshotId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus