{-# 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.UpdateVolume
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the configuration of an Amazon FSx for NetApp ONTAP or Amazon
-- FSx for OpenZFS volume.
module Amazonka.FSx.UpdateVolume
  ( -- * Creating a Request
    UpdateVolume (..),
    newUpdateVolume,

    -- * Request Lenses
    updateVolume_clientRequestToken,
    updateVolume_name,
    updateVolume_ontapConfiguration,
    updateVolume_openZFSConfiguration,
    updateVolume_volumeId,

    -- * Destructuring the Response
    UpdateVolumeResponse (..),
    newUpdateVolumeResponse,

    -- * Response Lenses
    updateVolumeResponse_volume,
    updateVolumeResponse_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:/ 'newUpdateVolume' smart constructor.
data UpdateVolume = UpdateVolume'
  { UpdateVolume -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the OpenZFS volume. OpenZFS root volumes are automatically
    -- named @FSX@. Child volume names must be unique among their parent
    -- volume\'s children. The name of the volume is part of the mount string
    -- for the OpenZFS volume.
    UpdateVolume -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The configuration of the ONTAP volume that you are updating.
    UpdateVolume -> Maybe UpdateOntapVolumeConfiguration
ontapConfiguration :: Prelude.Maybe UpdateOntapVolumeConfiguration,
    -- | The configuration of the OpenZFS volume that you are updating.
    UpdateVolume -> Maybe UpdateOpenZFSVolumeConfiguration
openZFSConfiguration :: Prelude.Maybe UpdateOpenZFSVolumeConfiguration,
    -- | The ID of the volume that you want to update, in the format
    -- @fsvol-0123456789abcdef0@.
    UpdateVolume -> Text
volumeId :: Prelude.Text
  }
  deriving (UpdateVolume -> UpdateVolume -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateVolume -> UpdateVolume -> Bool
$c/= :: UpdateVolume -> UpdateVolume -> Bool
== :: UpdateVolume -> UpdateVolume -> Bool
$c== :: UpdateVolume -> UpdateVolume -> Bool
Prelude.Eq, ReadPrec [UpdateVolume]
ReadPrec UpdateVolume
Int -> ReadS UpdateVolume
ReadS [UpdateVolume]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateVolume]
$creadListPrec :: ReadPrec [UpdateVolume]
readPrec :: ReadPrec UpdateVolume
$creadPrec :: ReadPrec UpdateVolume
readList :: ReadS [UpdateVolume]
$creadList :: ReadS [UpdateVolume]
readsPrec :: Int -> ReadS UpdateVolume
$creadsPrec :: Int -> ReadS UpdateVolume
Prelude.Read, Int -> UpdateVolume -> ShowS
[UpdateVolume] -> ShowS
UpdateVolume -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateVolume] -> ShowS
$cshowList :: [UpdateVolume] -> ShowS
show :: UpdateVolume -> String
$cshow :: UpdateVolume -> String
showsPrec :: Int -> UpdateVolume -> ShowS
$cshowsPrec :: Int -> UpdateVolume -> ShowS
Prelude.Show, forall x. Rep UpdateVolume x -> UpdateVolume
forall x. UpdateVolume -> Rep UpdateVolume x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateVolume x -> UpdateVolume
$cfrom :: forall x. UpdateVolume -> Rep UpdateVolume x
Prelude.Generic)

-- |
-- Create a value of 'UpdateVolume' 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', 'updateVolume_clientRequestToken' - Undocumented member.
--
-- 'name', 'updateVolume_name' - The name of the OpenZFS volume. OpenZFS root volumes are automatically
-- named @FSX@. Child volume names must be unique among their parent
-- volume\'s children. The name of the volume is part of the mount string
-- for the OpenZFS volume.
--
-- 'ontapConfiguration', 'updateVolume_ontapConfiguration' - The configuration of the ONTAP volume that you are updating.
--
-- 'openZFSConfiguration', 'updateVolume_openZFSConfiguration' - The configuration of the OpenZFS volume that you are updating.
--
-- 'volumeId', 'updateVolume_volumeId' - The ID of the volume that you want to update, in the format
-- @fsvol-0123456789abcdef0@.
newUpdateVolume ::
  -- | 'volumeId'
  Prelude.Text ->
  UpdateVolume
newUpdateVolume :: Text -> UpdateVolume
newUpdateVolume Text
pVolumeId_ =
  UpdateVolume'
    { $sel:clientRequestToken:UpdateVolume' :: Maybe Text
clientRequestToken = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateVolume' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:ontapConfiguration:UpdateVolume' :: Maybe UpdateOntapVolumeConfiguration
ontapConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:openZFSConfiguration:UpdateVolume' :: Maybe UpdateOpenZFSVolumeConfiguration
openZFSConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeId:UpdateVolume' :: Text
volumeId = Text
pVolumeId_
    }

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

-- | The name of the OpenZFS volume. OpenZFS root volumes are automatically
-- named @FSX@. Child volume names must be unique among their parent
-- volume\'s children. The name of the volume is part of the mount string
-- for the OpenZFS volume.
updateVolume_name :: Lens.Lens' UpdateVolume (Prelude.Maybe Prelude.Text)
updateVolume_name :: Lens' UpdateVolume (Maybe Text)
updateVolume_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateVolume' {Maybe Text
name :: Maybe Text
$sel:name:UpdateVolume' :: UpdateVolume -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateVolume
s@UpdateVolume' {} Maybe Text
a -> UpdateVolume
s {$sel:name:UpdateVolume' :: Maybe Text
name = Maybe Text
a} :: UpdateVolume)

-- | The configuration of the ONTAP volume that you are updating.
updateVolume_ontapConfiguration :: Lens.Lens' UpdateVolume (Prelude.Maybe UpdateOntapVolumeConfiguration)
updateVolume_ontapConfiguration :: Lens' UpdateVolume (Maybe UpdateOntapVolumeConfiguration)
updateVolume_ontapConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateVolume' {Maybe UpdateOntapVolumeConfiguration
ontapConfiguration :: Maybe UpdateOntapVolumeConfiguration
$sel:ontapConfiguration:UpdateVolume' :: UpdateVolume -> Maybe UpdateOntapVolumeConfiguration
ontapConfiguration} -> Maybe UpdateOntapVolumeConfiguration
ontapConfiguration) (\s :: UpdateVolume
s@UpdateVolume' {} Maybe UpdateOntapVolumeConfiguration
a -> UpdateVolume
s {$sel:ontapConfiguration:UpdateVolume' :: Maybe UpdateOntapVolumeConfiguration
ontapConfiguration = Maybe UpdateOntapVolumeConfiguration
a} :: UpdateVolume)

-- | The configuration of the OpenZFS volume that you are updating.
updateVolume_openZFSConfiguration :: Lens.Lens' UpdateVolume (Prelude.Maybe UpdateOpenZFSVolumeConfiguration)
updateVolume_openZFSConfiguration :: Lens' UpdateVolume (Maybe UpdateOpenZFSVolumeConfiguration)
updateVolume_openZFSConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateVolume' {Maybe UpdateOpenZFSVolumeConfiguration
openZFSConfiguration :: Maybe UpdateOpenZFSVolumeConfiguration
$sel:openZFSConfiguration:UpdateVolume' :: UpdateVolume -> Maybe UpdateOpenZFSVolumeConfiguration
openZFSConfiguration} -> Maybe UpdateOpenZFSVolumeConfiguration
openZFSConfiguration) (\s :: UpdateVolume
s@UpdateVolume' {} Maybe UpdateOpenZFSVolumeConfiguration
a -> UpdateVolume
s {$sel:openZFSConfiguration:UpdateVolume' :: Maybe UpdateOpenZFSVolumeConfiguration
openZFSConfiguration = Maybe UpdateOpenZFSVolumeConfiguration
a} :: UpdateVolume)

-- | The ID of the volume that you want to update, in the format
-- @fsvol-0123456789abcdef0@.
updateVolume_volumeId :: Lens.Lens' UpdateVolume Prelude.Text
updateVolume_volumeId :: Lens' UpdateVolume Text
updateVolume_volumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateVolume' {Text
volumeId :: Text
$sel:volumeId:UpdateVolume' :: UpdateVolume -> Text
volumeId} -> Text
volumeId) (\s :: UpdateVolume
s@UpdateVolume' {} Text
a -> UpdateVolume
s {$sel:volumeId:UpdateVolume' :: Text
volumeId = Text
a} :: UpdateVolume)

instance Core.AWSRequest UpdateVolume where
  type AWSResponse UpdateVolume = UpdateVolumeResponse
  request :: (Service -> Service) -> UpdateVolume -> Request UpdateVolume
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 UpdateVolume
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateVolume)))
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 Volume -> Int -> UpdateVolumeResponse
UpdateVolumeResponse'
            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
"Volume")
            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 UpdateVolume where
  hashWithSalt :: Int -> UpdateVolume -> Int
hashWithSalt Int
_salt UpdateVolume' {Maybe Text
Maybe UpdateOntapVolumeConfiguration
Maybe UpdateOpenZFSVolumeConfiguration
Text
volumeId :: Text
openZFSConfiguration :: Maybe UpdateOpenZFSVolumeConfiguration
ontapConfiguration :: Maybe UpdateOntapVolumeConfiguration
name :: Maybe Text
clientRequestToken :: Maybe Text
$sel:volumeId:UpdateVolume' :: UpdateVolume -> Text
$sel:openZFSConfiguration:UpdateVolume' :: UpdateVolume -> Maybe UpdateOpenZFSVolumeConfiguration
$sel:ontapConfiguration:UpdateVolume' :: UpdateVolume -> Maybe UpdateOntapVolumeConfiguration
$sel:name:UpdateVolume' :: UpdateVolume -> Maybe Text
$sel:clientRequestToken:UpdateVolume' :: UpdateVolume -> 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 Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UpdateOntapVolumeConfiguration
ontapConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UpdateOpenZFSVolumeConfiguration
openZFSConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
volumeId

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

instance Data.ToHeaders UpdateVolume where
  toHeaders :: UpdateVolume -> 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.UpdateVolume" ::
                          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 UpdateVolume where
  toJSON :: UpdateVolume -> Value
toJSON UpdateVolume' {Maybe Text
Maybe UpdateOntapVolumeConfiguration
Maybe UpdateOpenZFSVolumeConfiguration
Text
volumeId :: Text
openZFSConfiguration :: Maybe UpdateOpenZFSVolumeConfiguration
ontapConfiguration :: Maybe UpdateOntapVolumeConfiguration
name :: Maybe Text
clientRequestToken :: Maybe Text
$sel:volumeId:UpdateVolume' :: UpdateVolume -> Text
$sel:openZFSConfiguration:UpdateVolume' :: UpdateVolume -> Maybe UpdateOpenZFSVolumeConfiguration
$sel:ontapConfiguration:UpdateVolume' :: UpdateVolume -> Maybe UpdateOntapVolumeConfiguration
$sel:name:UpdateVolume' :: UpdateVolume -> Maybe Text
$sel:clientRequestToken:UpdateVolume' :: UpdateVolume -> 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
"Name" 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
name,
            (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 UpdateOntapVolumeConfiguration
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 UpdateOpenZFSVolumeConfiguration
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 UpdateVolume where
  toPath :: UpdateVolume -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newUpdateVolumeResponse' smart constructor.
data UpdateVolumeResponse = UpdateVolumeResponse'
  { -- | A description of the volume just updated. Returned after a successful
    -- @UpdateVolume@ API operation.
    UpdateVolumeResponse -> Maybe Volume
volume :: Prelude.Maybe Volume,
    -- | The response's http status code.
    UpdateVolumeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateVolumeResponse -> UpdateVolumeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateVolumeResponse -> UpdateVolumeResponse -> Bool
$c/= :: UpdateVolumeResponse -> UpdateVolumeResponse -> Bool
== :: UpdateVolumeResponse -> UpdateVolumeResponse -> Bool
$c== :: UpdateVolumeResponse -> UpdateVolumeResponse -> Bool
Prelude.Eq, ReadPrec [UpdateVolumeResponse]
ReadPrec UpdateVolumeResponse
Int -> ReadS UpdateVolumeResponse
ReadS [UpdateVolumeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateVolumeResponse]
$creadListPrec :: ReadPrec [UpdateVolumeResponse]
readPrec :: ReadPrec UpdateVolumeResponse
$creadPrec :: ReadPrec UpdateVolumeResponse
readList :: ReadS [UpdateVolumeResponse]
$creadList :: ReadS [UpdateVolumeResponse]
readsPrec :: Int -> ReadS UpdateVolumeResponse
$creadsPrec :: Int -> ReadS UpdateVolumeResponse
Prelude.Read, Int -> UpdateVolumeResponse -> ShowS
[UpdateVolumeResponse] -> ShowS
UpdateVolumeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateVolumeResponse] -> ShowS
$cshowList :: [UpdateVolumeResponse] -> ShowS
show :: UpdateVolumeResponse -> String
$cshow :: UpdateVolumeResponse -> String
showsPrec :: Int -> UpdateVolumeResponse -> ShowS
$cshowsPrec :: Int -> UpdateVolumeResponse -> ShowS
Prelude.Show, forall x. Rep UpdateVolumeResponse x -> UpdateVolumeResponse
forall x. UpdateVolumeResponse -> Rep UpdateVolumeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateVolumeResponse x -> UpdateVolumeResponse
$cfrom :: forall x. UpdateVolumeResponse -> Rep UpdateVolumeResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateVolumeResponse' 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:
--
-- 'volume', 'updateVolumeResponse_volume' - A description of the volume just updated. Returned after a successful
-- @UpdateVolume@ API operation.
--
-- 'httpStatus', 'updateVolumeResponse_httpStatus' - The response's http status code.
newUpdateVolumeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateVolumeResponse
newUpdateVolumeResponse :: Int -> UpdateVolumeResponse
newUpdateVolumeResponse Int
pHttpStatus_ =
  UpdateVolumeResponse'
    { $sel:volume:UpdateVolumeResponse' :: Maybe Volume
volume = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateVolumeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A description of the volume just updated. Returned after a successful
-- @UpdateVolume@ API operation.
updateVolumeResponse_volume :: Lens.Lens' UpdateVolumeResponse (Prelude.Maybe Volume)
updateVolumeResponse_volume :: Lens' UpdateVolumeResponse (Maybe Volume)
updateVolumeResponse_volume = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateVolumeResponse' {Maybe Volume
volume :: Maybe Volume
$sel:volume:UpdateVolumeResponse' :: UpdateVolumeResponse -> Maybe Volume
volume} -> Maybe Volume
volume) (\s :: UpdateVolumeResponse
s@UpdateVolumeResponse' {} Maybe Volume
a -> UpdateVolumeResponse
s {$sel:volume:UpdateVolumeResponse' :: Maybe Volume
volume = Maybe Volume
a} :: UpdateVolumeResponse)

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

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