{-# 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.EC2.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 the specified snapshot.
--
-- When you make periodic snapshots of a volume, the snapshots are
-- incremental, and only the blocks on the device that have changed since
-- your last snapshot are saved in the new snapshot. When you delete a
-- snapshot, only the data not needed for any other snapshot is removed. So
-- regardless of which prior snapshots have been deleted, all active
-- snapshots will have access to all the information needed to restore the
-- volume.
--
-- You cannot delete a snapshot of the root device of an EBS volume used by
-- a registered AMI. You must first de-register the AMI before you can
-- delete the snapshot.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ebs-deleting-snapshot.html Delete an Amazon EBS snapshot>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.DeleteSnapshot
  ( -- * Creating a Request
    DeleteSnapshot (..),
    newDeleteSnapshot,

    -- * Request Lenses
    deleteSnapshot_dryRun,
    deleteSnapshot_snapshotId,

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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.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'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DeleteSnapshot -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the EBS snapshot.
    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:
--
-- 'dryRun', 'deleteSnapshot_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'snapshotId', 'deleteSnapshot_snapshotId' - The ID of the EBS snapshot.
newDeleteSnapshot ::
  -- | 'snapshotId'
  Prelude.Text ->
  DeleteSnapshot
newDeleteSnapshot :: Text -> DeleteSnapshot
newDeleteSnapshot Text
pSnapshotId_ =
  DeleteSnapshot'
    { $sel:dryRun:DeleteSnapshot' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotId:DeleteSnapshot' :: Text
snapshotId = Text
pSnapshotId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
deleteSnapshot_dryRun :: Lens.Lens' DeleteSnapshot (Prelude.Maybe Prelude.Bool)
deleteSnapshot_dryRun :: Lens' DeleteSnapshot (Maybe Bool)
deleteSnapshot_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSnapshot' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteSnapshot' :: DeleteSnapshot -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteSnapshot
s@DeleteSnapshot' {} Maybe Bool
a -> DeleteSnapshot
s {$sel:dryRun:DeleteSnapshot' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteSnapshot)

-- | The ID of the EBS snapshot.
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 => 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 =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteSnapshotResponse
DeleteSnapshotResponse'

instance Prelude.Hashable DeleteSnapshot where
  hashWithSalt :: Int -> DeleteSnapshot -> Int
hashWithSalt Int
_salt DeleteSnapshot' {Maybe Bool
Text
snapshotId :: Text
dryRun :: Maybe Bool
$sel:snapshotId:DeleteSnapshot' :: DeleteSnapshot -> Text
$sel:dryRun:DeleteSnapshot' :: DeleteSnapshot -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotId

instance Prelude.NFData DeleteSnapshot where
  rnf :: DeleteSnapshot -> ()
rnf DeleteSnapshot' {Maybe Bool
Text
snapshotId :: Text
dryRun :: Maybe Bool
$sel:snapshotId:DeleteSnapshot' :: DeleteSnapshot -> Text
$sel:dryRun:DeleteSnapshot' :: DeleteSnapshot -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      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 -> [Header]
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' {Maybe Bool
Text
snapshotId :: Text
dryRun :: Maybe Bool
$sel:snapshotId:DeleteSnapshot' :: DeleteSnapshot -> Text
$sel:dryRun:DeleteSnapshot' :: DeleteSnapshot -> Maybe Bool
..} =
    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
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"SnapshotId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
snapshotId
      ]

-- | /See:/ 'newDeleteSnapshotResponse' smart constructor.
data DeleteSnapshotResponse = DeleteSnapshotResponse'
  {
  }
  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.
newDeleteSnapshotResponse ::
  DeleteSnapshotResponse
newDeleteSnapshotResponse :: DeleteSnapshotResponse
newDeleteSnapshotResponse = DeleteSnapshotResponse
DeleteSnapshotResponse'

instance Prelude.NFData DeleteSnapshotResponse where
  rnf :: DeleteSnapshotResponse -> ()
rnf DeleteSnapshotResponse
_ = ()