{-# 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.StorageGateway.ListVolumes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the iSCSI stored volumes of a gateway. Results are sorted by
-- volume ARN. The response includes only the volume ARNs. If you want
-- additional volume information, use the DescribeStorediSCSIVolumes or the
-- DescribeCachediSCSIVolumes API.
--
-- The operation supports pagination. By default, the operation returns a
-- maximum of up to 100 volumes. You can optionally specify the @Limit@
-- field in the body to limit the number of volumes in the response. If the
-- number of volumes returned in the response is truncated, the response
-- includes a Marker field. You can use this Marker value in your
-- subsequent request to retrieve the next set of volumes. This operation
-- is only supported in the cached volume and stored volume gateway types.
--
-- This operation returns paginated results.
module Amazonka.StorageGateway.ListVolumes
  ( -- * Creating a Request
    ListVolumes (..),
    newListVolumes,

    -- * Request Lenses
    listVolumes_gatewayARN,
    listVolumes_limit,
    listVolumes_marker,

    -- * Destructuring the Response
    ListVolumesResponse (..),
    newListVolumesResponse,

    -- * Response Lenses
    listVolumesResponse_gatewayARN,
    listVolumesResponse_marker,
    listVolumesResponse_volumeInfos,
    listVolumesResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.StorageGateway.Types

-- | A JSON object that contains one or more of the following fields:
--
-- -   ListVolumesInput$Limit
--
-- -   ListVolumesInput$Marker
--
-- /See:/ 'newListVolumes' smart constructor.
data ListVolumes = ListVolumes'
  { ListVolumes -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | Specifies that the list of volumes returned be limited to the specified
    -- number of items.
    ListVolumes -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | A string that indicates the position at which to begin the returned list
    -- of volumes. Obtain the marker from the response of a previous List iSCSI
    -- Volumes request.
    ListVolumes -> Maybe Text
marker :: Prelude.Maybe Prelude.Text
  }
  deriving (ListVolumes -> ListVolumes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListVolumes -> ListVolumes -> Bool
$c/= :: ListVolumes -> ListVolumes -> Bool
== :: ListVolumes -> ListVolumes -> Bool
$c== :: ListVolumes -> ListVolumes -> Bool
Prelude.Eq, ReadPrec [ListVolumes]
ReadPrec ListVolumes
Int -> ReadS ListVolumes
ReadS [ListVolumes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListVolumes]
$creadListPrec :: ReadPrec [ListVolumes]
readPrec :: ReadPrec ListVolumes
$creadPrec :: ReadPrec ListVolumes
readList :: ReadS [ListVolumes]
$creadList :: ReadS [ListVolumes]
readsPrec :: Int -> ReadS ListVolumes
$creadsPrec :: Int -> ReadS ListVolumes
Prelude.Read, Int -> ListVolumes -> ShowS
[ListVolumes] -> ShowS
ListVolumes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListVolumes] -> ShowS
$cshowList :: [ListVolumes] -> ShowS
show :: ListVolumes -> String
$cshow :: ListVolumes -> String
showsPrec :: Int -> ListVolumes -> ShowS
$cshowsPrec :: Int -> ListVolumes -> ShowS
Prelude.Show, forall x. Rep ListVolumes x -> ListVolumes
forall x. ListVolumes -> Rep ListVolumes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListVolumes x -> ListVolumes
$cfrom :: forall x. ListVolumes -> Rep ListVolumes x
Prelude.Generic)

-- |
-- Create a value of 'ListVolumes' 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:
--
-- 'gatewayARN', 'listVolumes_gatewayARN' - Undocumented member.
--
-- 'limit', 'listVolumes_limit' - Specifies that the list of volumes returned be limited to the specified
-- number of items.
--
-- 'marker', 'listVolumes_marker' - A string that indicates the position at which to begin the returned list
-- of volumes. Obtain the marker from the response of a previous List iSCSI
-- Volumes request.
newListVolumes ::
  ListVolumes
newListVolumes :: ListVolumes
newListVolumes =
  ListVolumes'
    { $sel:gatewayARN:ListVolumes' :: Maybe Text
gatewayARN = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListVolumes' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListVolumes' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing
    }

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

-- | Specifies that the list of volumes returned be limited to the specified
-- number of items.
listVolumes_limit :: Lens.Lens' ListVolumes (Prelude.Maybe Prelude.Natural)
listVolumes_limit :: Lens' ListVolumes (Maybe Natural)
listVolumes_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVolumes' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListVolumes' :: ListVolumes -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListVolumes
s@ListVolumes' {} Maybe Natural
a -> ListVolumes
s {$sel:limit:ListVolumes' :: Maybe Natural
limit = Maybe Natural
a} :: ListVolumes)

-- | A string that indicates the position at which to begin the returned list
-- of volumes. Obtain the marker from the response of a previous List iSCSI
-- Volumes request.
listVolumes_marker :: Lens.Lens' ListVolumes (Prelude.Maybe Prelude.Text)
listVolumes_marker :: Lens' ListVolumes (Maybe Text)
listVolumes_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVolumes' {Maybe Text
marker :: Maybe Text
$sel:marker:ListVolumes' :: ListVolumes -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListVolumes
s@ListVolumes' {} Maybe Text
a -> ListVolumes
s {$sel:marker:ListVolumes' :: Maybe Text
marker = Maybe Text
a} :: ListVolumes)

instance Core.AWSPager ListVolumes where
  page :: ListVolumes -> AWSResponse ListVolumes -> Maybe ListVolumes
page ListVolumes
rq AWSResponse ListVolumes
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListVolumes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVolumesResponse (Maybe Text)
listVolumesResponse_marker
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListVolumes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVolumesResponse (Maybe [VolumeInfo])
listVolumesResponse_volumeInfos
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListVolumes
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListVolumes (Maybe Text)
listVolumes_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListVolumes
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVolumesResponse (Maybe Text)
listVolumesResponse_marker
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListVolumes where
  type AWSResponse ListVolumes = ListVolumesResponse
  request :: (Service -> Service) -> ListVolumes -> Request ListVolumes
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 ListVolumes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListVolumes)))
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 Text
-> Maybe Text -> Maybe [VolumeInfo] -> Int -> ListVolumesResponse
ListVolumesResponse'
            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
"GatewayARN")
            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
"Marker")
            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
"VolumeInfos" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 ListVolumes where
  hashWithSalt :: Int -> ListVolumes -> Int
hashWithSalt Int
_salt ListVolumes' {Maybe Natural
Maybe Text
marker :: Maybe Text
limit :: Maybe Natural
gatewayARN :: Maybe Text
$sel:marker:ListVolumes' :: ListVolumes -> Maybe Text
$sel:limit:ListVolumes' :: ListVolumes -> Maybe Natural
$sel:gatewayARN:ListVolumes' :: ListVolumes -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gatewayARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker

instance Prelude.NFData ListVolumes where
  rnf :: ListVolumes -> ()
rnf ListVolumes' {Maybe Natural
Maybe Text
marker :: Maybe Text
limit :: Maybe Natural
gatewayARN :: Maybe Text
$sel:marker:ListVolumes' :: ListVolumes -> Maybe Text
$sel:limit:ListVolumes' :: ListVolumes -> Maybe Natural
$sel:gatewayARN:ListVolumes' :: ListVolumes -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker

instance Data.ToHeaders ListVolumes where
  toHeaders :: ListVolumes -> 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
"StorageGateway_20130630.ListVolumes" ::
                          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 ListVolumes where
  toJSON :: ListVolumes -> Value
toJSON ListVolumes' {Maybe Natural
Maybe Text
marker :: Maybe Text
limit :: Maybe Natural
gatewayARN :: Maybe Text
$sel:marker:ListVolumes' :: ListVolumes -> Maybe Text
$sel:limit:ListVolumes' :: ListVolumes -> Maybe Natural
$sel:gatewayARN:ListVolumes' :: ListVolumes -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"GatewayARN" 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
gatewayARN,
            (Key
"Limit" 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 Natural
limit,
            (Key
"Marker" 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
marker
          ]
      )

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

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

-- | A JSON object containing the following fields:
--
-- -   ListVolumesOutput$Marker
--
-- -   ListVolumesOutput$VolumeInfos
--
-- /See:/ 'newListVolumesResponse' smart constructor.
data ListVolumesResponse = ListVolumesResponse'
  { ListVolumesResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | Use the marker in your next request to continue pagination of iSCSI
    -- volumes. If there are no more volumes to list, this field does not
    -- appear in the response body.
    ListVolumesResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | An array of VolumeInfo objects, where each object describes an iSCSI
    -- volume. If no volumes are defined for the gateway, then @VolumeInfos@ is
    -- an empty array \"[]\".
    ListVolumesResponse -> Maybe [VolumeInfo]
volumeInfos :: Prelude.Maybe [VolumeInfo],
    -- | The response's http status code.
    ListVolumesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListVolumesResponse -> ListVolumesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListVolumesResponse -> ListVolumesResponse -> Bool
$c/= :: ListVolumesResponse -> ListVolumesResponse -> Bool
== :: ListVolumesResponse -> ListVolumesResponse -> Bool
$c== :: ListVolumesResponse -> ListVolumesResponse -> Bool
Prelude.Eq, ReadPrec [ListVolumesResponse]
ReadPrec ListVolumesResponse
Int -> ReadS ListVolumesResponse
ReadS [ListVolumesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListVolumesResponse]
$creadListPrec :: ReadPrec [ListVolumesResponse]
readPrec :: ReadPrec ListVolumesResponse
$creadPrec :: ReadPrec ListVolumesResponse
readList :: ReadS [ListVolumesResponse]
$creadList :: ReadS [ListVolumesResponse]
readsPrec :: Int -> ReadS ListVolumesResponse
$creadsPrec :: Int -> ReadS ListVolumesResponse
Prelude.Read, Int -> ListVolumesResponse -> ShowS
[ListVolumesResponse] -> ShowS
ListVolumesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListVolumesResponse] -> ShowS
$cshowList :: [ListVolumesResponse] -> ShowS
show :: ListVolumesResponse -> String
$cshow :: ListVolumesResponse -> String
showsPrec :: Int -> ListVolumesResponse -> ShowS
$cshowsPrec :: Int -> ListVolumesResponse -> ShowS
Prelude.Show, forall x. Rep ListVolumesResponse x -> ListVolumesResponse
forall x. ListVolumesResponse -> Rep ListVolumesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListVolumesResponse x -> ListVolumesResponse
$cfrom :: forall x. ListVolumesResponse -> Rep ListVolumesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListVolumesResponse' 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:
--
-- 'gatewayARN', 'listVolumesResponse_gatewayARN' - Undocumented member.
--
-- 'marker', 'listVolumesResponse_marker' - Use the marker in your next request to continue pagination of iSCSI
-- volumes. If there are no more volumes to list, this field does not
-- appear in the response body.
--
-- 'volumeInfos', 'listVolumesResponse_volumeInfos' - An array of VolumeInfo objects, where each object describes an iSCSI
-- volume. If no volumes are defined for the gateway, then @VolumeInfos@ is
-- an empty array \"[]\".
--
-- 'httpStatus', 'listVolumesResponse_httpStatus' - The response's http status code.
newListVolumesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListVolumesResponse
newListVolumesResponse :: Int -> ListVolumesResponse
newListVolumesResponse Int
pHttpStatus_ =
  ListVolumesResponse'
    { $sel:gatewayARN:ListVolumesResponse' :: Maybe Text
gatewayARN = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListVolumesResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeInfos:ListVolumesResponse' :: Maybe [VolumeInfo]
volumeInfos = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListVolumesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | Use the marker in your next request to continue pagination of iSCSI
-- volumes. If there are no more volumes to list, this field does not
-- appear in the response body.
listVolumesResponse_marker :: Lens.Lens' ListVolumesResponse (Prelude.Maybe Prelude.Text)
listVolumesResponse_marker :: Lens' ListVolumesResponse (Maybe Text)
listVolumesResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVolumesResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:ListVolumesResponse' :: ListVolumesResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListVolumesResponse
s@ListVolumesResponse' {} Maybe Text
a -> ListVolumesResponse
s {$sel:marker:ListVolumesResponse' :: Maybe Text
marker = Maybe Text
a} :: ListVolumesResponse)

-- | An array of VolumeInfo objects, where each object describes an iSCSI
-- volume. If no volumes are defined for the gateway, then @VolumeInfos@ is
-- an empty array \"[]\".
listVolumesResponse_volumeInfos :: Lens.Lens' ListVolumesResponse (Prelude.Maybe [VolumeInfo])
listVolumesResponse_volumeInfos :: Lens' ListVolumesResponse (Maybe [VolumeInfo])
listVolumesResponse_volumeInfos = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVolumesResponse' {Maybe [VolumeInfo]
volumeInfos :: Maybe [VolumeInfo]
$sel:volumeInfos:ListVolumesResponse' :: ListVolumesResponse -> Maybe [VolumeInfo]
volumeInfos} -> Maybe [VolumeInfo]
volumeInfos) (\s :: ListVolumesResponse
s@ListVolumesResponse' {} Maybe [VolumeInfo]
a -> ListVolumesResponse
s {$sel:volumeInfos:ListVolumesResponse' :: Maybe [VolumeInfo]
volumeInfos = Maybe [VolumeInfo]
a} :: ListVolumesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData ListVolumesResponse where
  rnf :: ListVolumesResponse -> ()
rnf ListVolumesResponse' {Int
Maybe [VolumeInfo]
Maybe Text
httpStatus :: Int
volumeInfos :: Maybe [VolumeInfo]
marker :: Maybe Text
gatewayARN :: Maybe Text
$sel:httpStatus:ListVolumesResponse' :: ListVolumesResponse -> Int
$sel:volumeInfos:ListVolumesResponse' :: ListVolumesResponse -> Maybe [VolumeInfo]
$sel:marker:ListVolumesResponse' :: ListVolumesResponse -> Maybe Text
$sel:gatewayARN:ListVolumesResponse' :: ListVolumesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [VolumeInfo]
volumeInfos
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus