{-# 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.DeleteVolume
-- 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 NetApp ONTAP or Amazon FSx for OpenZFS volume.
module Amazonka.FSx.DeleteVolume
  ( -- * Creating a Request
    DeleteVolume (..),
    newDeleteVolume,

    -- * Request Lenses
    deleteVolume_clientRequestToken,
    deleteVolume_ontapConfiguration,
    deleteVolume_openZFSConfiguration,
    deleteVolume_volumeId,

    -- * Destructuring the Response
    DeleteVolumeResponse (..),
    newDeleteVolumeResponse,

    -- * Response Lenses
    deleteVolumeResponse_lifecycle,
    deleteVolumeResponse_ontapResponse,
    deleteVolumeResponse_volumeId,
    deleteVolumeResponse_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:/ 'newDeleteVolume' smart constructor.
data DeleteVolume = DeleteVolume'
  { DeleteVolume -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | For Amazon FSx for ONTAP volumes, specify whether to take a final backup
    -- of the volume and apply tags to the backup. To apply tags to the backup,
    -- you must have the @fsx:TagResource@ permission.
    DeleteVolume -> Maybe DeleteVolumeOntapConfiguration
ontapConfiguration :: Prelude.Maybe DeleteVolumeOntapConfiguration,
    -- | For Amazon FSx for OpenZFS volumes, specify whether to delete all child
    -- volumes and snapshots.
    DeleteVolume -> Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration :: Prelude.Maybe DeleteVolumeOpenZFSConfiguration,
    -- | The ID of the volume that you are deleting.
    DeleteVolume -> Text
volumeId :: Prelude.Text
  }
  deriving (DeleteVolume -> DeleteVolume -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVolume -> DeleteVolume -> Bool
$c/= :: DeleteVolume -> DeleteVolume -> Bool
== :: DeleteVolume -> DeleteVolume -> Bool
$c== :: DeleteVolume -> DeleteVolume -> Bool
Prelude.Eq, ReadPrec [DeleteVolume]
ReadPrec DeleteVolume
Int -> ReadS DeleteVolume
ReadS [DeleteVolume]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVolume]
$creadListPrec :: ReadPrec [DeleteVolume]
readPrec :: ReadPrec DeleteVolume
$creadPrec :: ReadPrec DeleteVolume
readList :: ReadS [DeleteVolume]
$creadList :: ReadS [DeleteVolume]
readsPrec :: Int -> ReadS DeleteVolume
$creadsPrec :: Int -> ReadS DeleteVolume
Prelude.Read, Int -> DeleteVolume -> ShowS
[DeleteVolume] -> ShowS
DeleteVolume -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVolume] -> ShowS
$cshowList :: [DeleteVolume] -> ShowS
show :: DeleteVolume -> String
$cshow :: DeleteVolume -> String
showsPrec :: Int -> DeleteVolume -> ShowS
$cshowsPrec :: Int -> DeleteVolume -> ShowS
Prelude.Show, forall x. Rep DeleteVolume x -> DeleteVolume
forall x. DeleteVolume -> Rep DeleteVolume x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteVolume x -> DeleteVolume
$cfrom :: forall x. DeleteVolume -> Rep DeleteVolume x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVolume' 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', 'deleteVolume_clientRequestToken' - Undocumented member.
--
-- 'ontapConfiguration', 'deleteVolume_ontapConfiguration' - For Amazon FSx for ONTAP volumes, specify whether to take a final backup
-- of the volume and apply tags to the backup. To apply tags to the backup,
-- you must have the @fsx:TagResource@ permission.
--
-- 'openZFSConfiguration', 'deleteVolume_openZFSConfiguration' - For Amazon FSx for OpenZFS volumes, specify whether to delete all child
-- volumes and snapshots.
--
-- 'volumeId', 'deleteVolume_volumeId' - The ID of the volume that you are deleting.
newDeleteVolume ::
  -- | 'volumeId'
  Prelude.Text ->
  DeleteVolume
newDeleteVolume :: Text -> DeleteVolume
newDeleteVolume Text
pVolumeId_ =
  DeleteVolume'
    { $sel:clientRequestToken:DeleteVolume' :: Maybe Text
clientRequestToken = forall a. Maybe a
Prelude.Nothing,
      $sel:ontapConfiguration:DeleteVolume' :: Maybe DeleteVolumeOntapConfiguration
ontapConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:openZFSConfiguration:DeleteVolume' :: Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeId:DeleteVolume' :: Text
volumeId = Text
pVolumeId_
    }

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

-- | For Amazon FSx for ONTAP volumes, specify whether to take a final backup
-- of the volume and apply tags to the backup. To apply tags to the backup,
-- you must have the @fsx:TagResource@ permission.
deleteVolume_ontapConfiguration :: Lens.Lens' DeleteVolume (Prelude.Maybe DeleteVolumeOntapConfiguration)
deleteVolume_ontapConfiguration :: Lens' DeleteVolume (Maybe DeleteVolumeOntapConfiguration)
deleteVolume_ontapConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVolume' {Maybe DeleteVolumeOntapConfiguration
ontapConfiguration :: Maybe DeleteVolumeOntapConfiguration
$sel:ontapConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOntapConfiguration
ontapConfiguration} -> Maybe DeleteVolumeOntapConfiguration
ontapConfiguration) (\s :: DeleteVolume
s@DeleteVolume' {} Maybe DeleteVolumeOntapConfiguration
a -> DeleteVolume
s {$sel:ontapConfiguration:DeleteVolume' :: Maybe DeleteVolumeOntapConfiguration
ontapConfiguration = Maybe DeleteVolumeOntapConfiguration
a} :: DeleteVolume)

-- | For Amazon FSx for OpenZFS volumes, specify whether to delete all child
-- volumes and snapshots.
deleteVolume_openZFSConfiguration :: Lens.Lens' DeleteVolume (Prelude.Maybe DeleteVolumeOpenZFSConfiguration)
deleteVolume_openZFSConfiguration :: Lens' DeleteVolume (Maybe DeleteVolumeOpenZFSConfiguration)
deleteVolume_openZFSConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVolume' {Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration :: Maybe DeleteVolumeOpenZFSConfiguration
$sel:openZFSConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration} -> Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration) (\s :: DeleteVolume
s@DeleteVolume' {} Maybe DeleteVolumeOpenZFSConfiguration
a -> DeleteVolume
s {$sel:openZFSConfiguration:DeleteVolume' :: Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration = Maybe DeleteVolumeOpenZFSConfiguration
a} :: DeleteVolume)

-- | The ID of the volume that you are deleting.
deleteVolume_volumeId :: Lens.Lens' DeleteVolume Prelude.Text
deleteVolume_volumeId :: Lens' DeleteVolume Text
deleteVolume_volumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVolume' {Text
volumeId :: Text
$sel:volumeId:DeleteVolume' :: DeleteVolume -> Text
volumeId} -> Text
volumeId) (\s :: DeleteVolume
s@DeleteVolume' {} Text
a -> DeleteVolume
s {$sel:volumeId:DeleteVolume' :: Text
volumeId = Text
a} :: DeleteVolume)

instance Core.AWSRequest DeleteVolume where
  type AWSResponse DeleteVolume = DeleteVolumeResponse
  request :: (Service -> Service) -> DeleteVolume -> Request DeleteVolume
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 DeleteVolume
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteVolume)))
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 VolumeLifecycle
-> Maybe DeleteVolumeOntapResponse
-> Maybe Text
-> Int
-> DeleteVolumeResponse
DeleteVolumeResponse'
            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
"OntapResponse")
            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
"VolumeId")
            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 DeleteVolume where
  hashWithSalt :: Int -> DeleteVolume -> Int
hashWithSalt Int
_salt DeleteVolume' {Maybe Text
Maybe DeleteVolumeOpenZFSConfiguration
Maybe DeleteVolumeOntapConfiguration
Text
volumeId :: Text
openZFSConfiguration :: Maybe DeleteVolumeOpenZFSConfiguration
ontapConfiguration :: Maybe DeleteVolumeOntapConfiguration
clientRequestToken :: Maybe Text
$sel:volumeId:DeleteVolume' :: DeleteVolume -> Text
$sel:openZFSConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOpenZFSConfiguration
$sel:ontapConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOntapConfiguration
$sel:clientRequestToken:DeleteVolume' :: DeleteVolume -> 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` Maybe DeleteVolumeOntapConfiguration
ontapConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
volumeId

instance Prelude.NFData DeleteVolume where
  rnf :: DeleteVolume -> ()
rnf DeleteVolume' {Maybe Text
Maybe DeleteVolumeOpenZFSConfiguration
Maybe DeleteVolumeOntapConfiguration
Text
volumeId :: Text
openZFSConfiguration :: Maybe DeleteVolumeOpenZFSConfiguration
ontapConfiguration :: Maybe DeleteVolumeOntapConfiguration
clientRequestToken :: Maybe Text
$sel:volumeId:DeleteVolume' :: DeleteVolume -> Text
$sel:openZFSConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOpenZFSConfiguration
$sel:ontapConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOntapConfiguration
$sel:clientRequestToken:DeleteVolume' :: DeleteVolume -> 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 Maybe DeleteVolumeOntapConfiguration
ontapConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeleteVolumeOpenZFSConfiguration
openZFSConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
volumeId

instance Data.ToHeaders DeleteVolume where
  toHeaders :: DeleteVolume -> 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.DeleteVolume" ::
                          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 DeleteVolume where
  toJSON :: DeleteVolume -> Value
toJSON DeleteVolume' {Maybe Text
Maybe DeleteVolumeOpenZFSConfiguration
Maybe DeleteVolumeOntapConfiguration
Text
volumeId :: Text
openZFSConfiguration :: Maybe DeleteVolumeOpenZFSConfiguration
ontapConfiguration :: Maybe DeleteVolumeOntapConfiguration
clientRequestToken :: Maybe Text
$sel:volumeId:DeleteVolume' :: DeleteVolume -> Text
$sel:openZFSConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOpenZFSConfiguration
$sel:ontapConfiguration:DeleteVolume' :: DeleteVolume -> Maybe DeleteVolumeOntapConfiguration
$sel:clientRequestToken:DeleteVolume' :: DeleteVolume -> 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,
            (Key
"OntapConfiguration" 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 DeleteVolumeOntapConfiguration
ontapConfiguration,
            (Key
"OpenZFSConfiguration" 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 DeleteVolumeOpenZFSConfiguration
openZFSConfiguration,
            forall a. a -> Maybe a
Prelude.Just (Key
"VolumeId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
volumeId)
          ]
      )

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

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

-- | /See:/ 'newDeleteVolumeResponse' smart constructor.
data DeleteVolumeResponse = DeleteVolumeResponse'
  { -- | The lifecycle state of the volume being deleted. If the @DeleteVolume@
    -- operation is successful, this value is @DELETING@.
    DeleteVolumeResponse -> Maybe VolumeLifecycle
lifecycle :: Prelude.Maybe VolumeLifecycle,
    -- | Returned after a @DeleteVolume@ request, showing the status of the
    -- delete request.
    DeleteVolumeResponse -> Maybe DeleteVolumeOntapResponse
ontapResponse :: Prelude.Maybe DeleteVolumeOntapResponse,
    -- | The ID of the volume that\'s being deleted.
    DeleteVolumeResponse -> Maybe Text
volumeId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteVolumeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteVolumeResponse -> DeleteVolumeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVolumeResponse -> DeleteVolumeResponse -> Bool
$c/= :: DeleteVolumeResponse -> DeleteVolumeResponse -> Bool
== :: DeleteVolumeResponse -> DeleteVolumeResponse -> Bool
$c== :: DeleteVolumeResponse -> DeleteVolumeResponse -> Bool
Prelude.Eq, ReadPrec [DeleteVolumeResponse]
ReadPrec DeleteVolumeResponse
Int -> ReadS DeleteVolumeResponse
ReadS [DeleteVolumeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVolumeResponse]
$creadListPrec :: ReadPrec [DeleteVolumeResponse]
readPrec :: ReadPrec DeleteVolumeResponse
$creadPrec :: ReadPrec DeleteVolumeResponse
readList :: ReadS [DeleteVolumeResponse]
$creadList :: ReadS [DeleteVolumeResponse]
readsPrec :: Int -> ReadS DeleteVolumeResponse
$creadsPrec :: Int -> ReadS DeleteVolumeResponse
Prelude.Read, Int -> DeleteVolumeResponse -> ShowS
[DeleteVolumeResponse] -> ShowS
DeleteVolumeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVolumeResponse] -> ShowS
$cshowList :: [DeleteVolumeResponse] -> ShowS
show :: DeleteVolumeResponse -> String
$cshow :: DeleteVolumeResponse -> String
showsPrec :: Int -> DeleteVolumeResponse -> ShowS
$cshowsPrec :: Int -> DeleteVolumeResponse -> ShowS
Prelude.Show, forall x. Rep DeleteVolumeResponse x -> DeleteVolumeResponse
forall x. DeleteVolumeResponse -> Rep DeleteVolumeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteVolumeResponse x -> DeleteVolumeResponse
$cfrom :: forall x. DeleteVolumeResponse -> Rep DeleteVolumeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVolumeResponse' 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', 'deleteVolumeResponse_lifecycle' - The lifecycle state of the volume being deleted. If the @DeleteVolume@
-- operation is successful, this value is @DELETING@.
--
-- 'ontapResponse', 'deleteVolumeResponse_ontapResponse' - Returned after a @DeleteVolume@ request, showing the status of the
-- delete request.
--
-- 'volumeId', 'deleteVolumeResponse_volumeId' - The ID of the volume that\'s being deleted.
--
-- 'httpStatus', 'deleteVolumeResponse_httpStatus' - The response's http status code.
newDeleteVolumeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteVolumeResponse
newDeleteVolumeResponse :: Int -> DeleteVolumeResponse
newDeleteVolumeResponse Int
pHttpStatus_ =
  DeleteVolumeResponse'
    { $sel:lifecycle:DeleteVolumeResponse' :: Maybe VolumeLifecycle
lifecycle = forall a. Maybe a
Prelude.Nothing,
      $sel:ontapResponse:DeleteVolumeResponse' :: Maybe DeleteVolumeOntapResponse
ontapResponse = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeId:DeleteVolumeResponse' :: Maybe Text
volumeId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteVolumeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The lifecycle state of the volume being deleted. If the @DeleteVolume@
-- operation is successful, this value is @DELETING@.
deleteVolumeResponse_lifecycle :: Lens.Lens' DeleteVolumeResponse (Prelude.Maybe VolumeLifecycle)
deleteVolumeResponse_lifecycle :: Lens' DeleteVolumeResponse (Maybe VolumeLifecycle)
deleteVolumeResponse_lifecycle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVolumeResponse' {Maybe VolumeLifecycle
lifecycle :: Maybe VolumeLifecycle
$sel:lifecycle:DeleteVolumeResponse' :: DeleteVolumeResponse -> Maybe VolumeLifecycle
lifecycle} -> Maybe VolumeLifecycle
lifecycle) (\s :: DeleteVolumeResponse
s@DeleteVolumeResponse' {} Maybe VolumeLifecycle
a -> DeleteVolumeResponse
s {$sel:lifecycle:DeleteVolumeResponse' :: Maybe VolumeLifecycle
lifecycle = Maybe VolumeLifecycle
a} :: DeleteVolumeResponse)

-- | Returned after a @DeleteVolume@ request, showing the status of the
-- delete request.
deleteVolumeResponse_ontapResponse :: Lens.Lens' DeleteVolumeResponse (Prelude.Maybe DeleteVolumeOntapResponse)
deleteVolumeResponse_ontapResponse :: Lens' DeleteVolumeResponse (Maybe DeleteVolumeOntapResponse)
deleteVolumeResponse_ontapResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVolumeResponse' {Maybe DeleteVolumeOntapResponse
ontapResponse :: Maybe DeleteVolumeOntapResponse
$sel:ontapResponse:DeleteVolumeResponse' :: DeleteVolumeResponse -> Maybe DeleteVolumeOntapResponse
ontapResponse} -> Maybe DeleteVolumeOntapResponse
ontapResponse) (\s :: DeleteVolumeResponse
s@DeleteVolumeResponse' {} Maybe DeleteVolumeOntapResponse
a -> DeleteVolumeResponse
s {$sel:ontapResponse:DeleteVolumeResponse' :: Maybe DeleteVolumeOntapResponse
ontapResponse = Maybe DeleteVolumeOntapResponse
a} :: DeleteVolumeResponse)

-- | The ID of the volume that\'s being deleted.
deleteVolumeResponse_volumeId :: Lens.Lens' DeleteVolumeResponse (Prelude.Maybe Prelude.Text)
deleteVolumeResponse_volumeId :: Lens' DeleteVolumeResponse (Maybe Text)
deleteVolumeResponse_volumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVolumeResponse' {Maybe Text
volumeId :: Maybe Text
$sel:volumeId:DeleteVolumeResponse' :: DeleteVolumeResponse -> Maybe Text
volumeId} -> Maybe Text
volumeId) (\s :: DeleteVolumeResponse
s@DeleteVolumeResponse' {} Maybe Text
a -> DeleteVolumeResponse
s {$sel:volumeId:DeleteVolumeResponse' :: Maybe Text
volumeId = Maybe Text
a} :: DeleteVolumeResponse)

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

instance Prelude.NFData DeleteVolumeResponse where
  rnf :: DeleteVolumeResponse -> ()
rnf DeleteVolumeResponse' {Int
Maybe Text
Maybe DeleteVolumeOntapResponse
Maybe VolumeLifecycle
httpStatus :: Int
volumeId :: Maybe Text
ontapResponse :: Maybe DeleteVolumeOntapResponse
lifecycle :: Maybe VolumeLifecycle
$sel:httpStatus:DeleteVolumeResponse' :: DeleteVolumeResponse -> Int
$sel:volumeId:DeleteVolumeResponse' :: DeleteVolumeResponse -> Maybe Text
$sel:ontapResponse:DeleteVolumeResponse' :: DeleteVolumeResponse -> Maybe DeleteVolumeOntapResponse
$sel:lifecycle:DeleteVolumeResponse' :: DeleteVolumeResponse -> Maybe VolumeLifecycle
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe VolumeLifecycle
lifecycle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeleteVolumeOntapResponse
ontapResponse
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
volumeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus