{-# 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.DescribeCachediSCSIVolumes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a description of the gateway volumes specified in the request.
-- This operation is only supported in the cached volume gateway types.
--
-- The list of gateway volumes in the request must be from one gateway. In
-- the response, Storage Gateway returns volume information sorted by
-- volume Amazon Resource Name (ARN).
module Amazonka.StorageGateway.DescribeCachediSCSIVolumes
  ( -- * Creating a Request
    DescribeCachediSCSIVolumes (..),
    newDescribeCachediSCSIVolumes,

    -- * Request Lenses
    describeCachediSCSIVolumes_volumeARNs,

    -- * Destructuring the Response
    DescribeCachediSCSIVolumesResponse (..),
    newDescribeCachediSCSIVolumesResponse,

    -- * Response Lenses
    describeCachediSCSIVolumesResponse_cachediSCSIVolumes,
    describeCachediSCSIVolumesResponse_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

-- | /See:/ 'newDescribeCachediSCSIVolumes' smart constructor.
data DescribeCachediSCSIVolumes = DescribeCachediSCSIVolumes'
  { -- | An array of strings where each string represents the Amazon Resource
    -- Name (ARN) of a cached volume. All of the specified cached volumes must
    -- be from the same gateway. Use ListVolumes to get volume ARNs for a
    -- gateway.
    DescribeCachediSCSIVolumes -> [Text]
volumeARNs :: [Prelude.Text]
  }
  deriving (DescribeCachediSCSIVolumes -> DescribeCachediSCSIVolumes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCachediSCSIVolumes -> DescribeCachediSCSIVolumes -> Bool
$c/= :: DescribeCachediSCSIVolumes -> DescribeCachediSCSIVolumes -> Bool
== :: DescribeCachediSCSIVolumes -> DescribeCachediSCSIVolumes -> Bool
$c== :: DescribeCachediSCSIVolumes -> DescribeCachediSCSIVolumes -> Bool
Prelude.Eq, ReadPrec [DescribeCachediSCSIVolumes]
ReadPrec DescribeCachediSCSIVolumes
Int -> ReadS DescribeCachediSCSIVolumes
ReadS [DescribeCachediSCSIVolumes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCachediSCSIVolumes]
$creadListPrec :: ReadPrec [DescribeCachediSCSIVolumes]
readPrec :: ReadPrec DescribeCachediSCSIVolumes
$creadPrec :: ReadPrec DescribeCachediSCSIVolumes
readList :: ReadS [DescribeCachediSCSIVolumes]
$creadList :: ReadS [DescribeCachediSCSIVolumes]
readsPrec :: Int -> ReadS DescribeCachediSCSIVolumes
$creadsPrec :: Int -> ReadS DescribeCachediSCSIVolumes
Prelude.Read, Int -> DescribeCachediSCSIVolumes -> ShowS
[DescribeCachediSCSIVolumes] -> ShowS
DescribeCachediSCSIVolumes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCachediSCSIVolumes] -> ShowS
$cshowList :: [DescribeCachediSCSIVolumes] -> ShowS
show :: DescribeCachediSCSIVolumes -> String
$cshow :: DescribeCachediSCSIVolumes -> String
showsPrec :: Int -> DescribeCachediSCSIVolumes -> ShowS
$cshowsPrec :: Int -> DescribeCachediSCSIVolumes -> ShowS
Prelude.Show, forall x.
Rep DescribeCachediSCSIVolumes x -> DescribeCachediSCSIVolumes
forall x.
DescribeCachediSCSIVolumes -> Rep DescribeCachediSCSIVolumes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCachediSCSIVolumes x -> DescribeCachediSCSIVolumes
$cfrom :: forall x.
DescribeCachediSCSIVolumes -> Rep DescribeCachediSCSIVolumes x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCachediSCSIVolumes' 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:
--
-- 'volumeARNs', 'describeCachediSCSIVolumes_volumeARNs' - An array of strings where each string represents the Amazon Resource
-- Name (ARN) of a cached volume. All of the specified cached volumes must
-- be from the same gateway. Use ListVolumes to get volume ARNs for a
-- gateway.
newDescribeCachediSCSIVolumes ::
  DescribeCachediSCSIVolumes
newDescribeCachediSCSIVolumes :: DescribeCachediSCSIVolumes
newDescribeCachediSCSIVolumes =
  DescribeCachediSCSIVolumes'
    { $sel:volumeARNs:DescribeCachediSCSIVolumes' :: [Text]
volumeARNs =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | An array of strings where each string represents the Amazon Resource
-- Name (ARN) of a cached volume. All of the specified cached volumes must
-- be from the same gateway. Use ListVolumes to get volume ARNs for a
-- gateway.
describeCachediSCSIVolumes_volumeARNs :: Lens.Lens' DescribeCachediSCSIVolumes [Prelude.Text]
describeCachediSCSIVolumes_volumeARNs :: Lens' DescribeCachediSCSIVolumes [Text]
describeCachediSCSIVolumes_volumeARNs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCachediSCSIVolumes' {[Text]
volumeARNs :: [Text]
$sel:volumeARNs:DescribeCachediSCSIVolumes' :: DescribeCachediSCSIVolumes -> [Text]
volumeARNs} -> [Text]
volumeARNs) (\s :: DescribeCachediSCSIVolumes
s@DescribeCachediSCSIVolumes' {} [Text]
a -> DescribeCachediSCSIVolumes
s {$sel:volumeARNs:DescribeCachediSCSIVolumes' :: [Text]
volumeARNs = [Text]
a} :: DescribeCachediSCSIVolumes) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest DescribeCachediSCSIVolumes where
  type
    AWSResponse DescribeCachediSCSIVolumes =
      DescribeCachediSCSIVolumesResponse
  request :: (Service -> Service)
-> DescribeCachediSCSIVolumes -> Request DescribeCachediSCSIVolumes
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 DescribeCachediSCSIVolumes
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeCachediSCSIVolumes)))
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 [CachediSCSIVolume]
-> Int -> DescribeCachediSCSIVolumesResponse
DescribeCachediSCSIVolumesResponse'
            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
"CachediSCSIVolumes"
                            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 DescribeCachediSCSIVolumes where
  hashWithSalt :: Int -> DescribeCachediSCSIVolumes -> Int
hashWithSalt Int
_salt DescribeCachediSCSIVolumes' {[Text]
volumeARNs :: [Text]
$sel:volumeARNs:DescribeCachediSCSIVolumes' :: DescribeCachediSCSIVolumes -> [Text]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
volumeARNs

instance Prelude.NFData DescribeCachediSCSIVolumes where
  rnf :: DescribeCachediSCSIVolumes -> ()
rnf DescribeCachediSCSIVolumes' {[Text]
volumeARNs :: [Text]
$sel:volumeARNs:DescribeCachediSCSIVolumes' :: DescribeCachediSCSIVolumes -> [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [Text]
volumeARNs

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

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

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

-- | A JSON object containing the following fields:
--
-- /See:/ 'newDescribeCachediSCSIVolumesResponse' smart constructor.
data DescribeCachediSCSIVolumesResponse = DescribeCachediSCSIVolumesResponse'
  { -- | An array of objects where each object contains metadata about one cached
    -- volume.
    DescribeCachediSCSIVolumesResponse -> Maybe [CachediSCSIVolume]
cachediSCSIVolumes :: Prelude.Maybe [CachediSCSIVolume],
    -- | The response's http status code.
    DescribeCachediSCSIVolumesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeCachediSCSIVolumesResponse
-> DescribeCachediSCSIVolumesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCachediSCSIVolumesResponse
-> DescribeCachediSCSIVolumesResponse -> Bool
$c/= :: DescribeCachediSCSIVolumesResponse
-> DescribeCachediSCSIVolumesResponse -> Bool
== :: DescribeCachediSCSIVolumesResponse
-> DescribeCachediSCSIVolumesResponse -> Bool
$c== :: DescribeCachediSCSIVolumesResponse
-> DescribeCachediSCSIVolumesResponse -> Bool
Prelude.Eq, ReadPrec [DescribeCachediSCSIVolumesResponse]
ReadPrec DescribeCachediSCSIVolumesResponse
Int -> ReadS DescribeCachediSCSIVolumesResponse
ReadS [DescribeCachediSCSIVolumesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCachediSCSIVolumesResponse]
$creadListPrec :: ReadPrec [DescribeCachediSCSIVolumesResponse]
readPrec :: ReadPrec DescribeCachediSCSIVolumesResponse
$creadPrec :: ReadPrec DescribeCachediSCSIVolumesResponse
readList :: ReadS [DescribeCachediSCSIVolumesResponse]
$creadList :: ReadS [DescribeCachediSCSIVolumesResponse]
readsPrec :: Int -> ReadS DescribeCachediSCSIVolumesResponse
$creadsPrec :: Int -> ReadS DescribeCachediSCSIVolumesResponse
Prelude.Read, Int -> DescribeCachediSCSIVolumesResponse -> ShowS
[DescribeCachediSCSIVolumesResponse] -> ShowS
DescribeCachediSCSIVolumesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCachediSCSIVolumesResponse] -> ShowS
$cshowList :: [DescribeCachediSCSIVolumesResponse] -> ShowS
show :: DescribeCachediSCSIVolumesResponse -> String
$cshow :: DescribeCachediSCSIVolumesResponse -> String
showsPrec :: Int -> DescribeCachediSCSIVolumesResponse -> ShowS
$cshowsPrec :: Int -> DescribeCachediSCSIVolumesResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeCachediSCSIVolumesResponse x
-> DescribeCachediSCSIVolumesResponse
forall x.
DescribeCachediSCSIVolumesResponse
-> Rep DescribeCachediSCSIVolumesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCachediSCSIVolumesResponse x
-> DescribeCachediSCSIVolumesResponse
$cfrom :: forall x.
DescribeCachediSCSIVolumesResponse
-> Rep DescribeCachediSCSIVolumesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCachediSCSIVolumesResponse' 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:
--
-- 'cachediSCSIVolumes', 'describeCachediSCSIVolumesResponse_cachediSCSIVolumes' - An array of objects where each object contains metadata about one cached
-- volume.
--
-- 'httpStatus', 'describeCachediSCSIVolumesResponse_httpStatus' - The response's http status code.
newDescribeCachediSCSIVolumesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeCachediSCSIVolumesResponse
newDescribeCachediSCSIVolumesResponse :: Int -> DescribeCachediSCSIVolumesResponse
newDescribeCachediSCSIVolumesResponse Int
pHttpStatus_ =
  DescribeCachediSCSIVolumesResponse'
    { $sel:cachediSCSIVolumes:DescribeCachediSCSIVolumesResponse' :: Maybe [CachediSCSIVolume]
cachediSCSIVolumes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeCachediSCSIVolumesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects where each object contains metadata about one cached
-- volume.
describeCachediSCSIVolumesResponse_cachediSCSIVolumes :: Lens.Lens' DescribeCachediSCSIVolumesResponse (Prelude.Maybe [CachediSCSIVolume])
describeCachediSCSIVolumesResponse_cachediSCSIVolumes :: Lens'
  DescribeCachediSCSIVolumesResponse (Maybe [CachediSCSIVolume])
describeCachediSCSIVolumesResponse_cachediSCSIVolumes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCachediSCSIVolumesResponse' {Maybe [CachediSCSIVolume]
cachediSCSIVolumes :: Maybe [CachediSCSIVolume]
$sel:cachediSCSIVolumes:DescribeCachediSCSIVolumesResponse' :: DescribeCachediSCSIVolumesResponse -> Maybe [CachediSCSIVolume]
cachediSCSIVolumes} -> Maybe [CachediSCSIVolume]
cachediSCSIVolumes) (\s :: DescribeCachediSCSIVolumesResponse
s@DescribeCachediSCSIVolumesResponse' {} Maybe [CachediSCSIVolume]
a -> DescribeCachediSCSIVolumesResponse
s {$sel:cachediSCSIVolumes:DescribeCachediSCSIVolumesResponse' :: Maybe [CachediSCSIVolume]
cachediSCSIVolumes = Maybe [CachediSCSIVolume]
a} :: DescribeCachediSCSIVolumesResponse) 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.
describeCachediSCSIVolumesResponse_httpStatus :: Lens.Lens' DescribeCachediSCSIVolumesResponse Prelude.Int
describeCachediSCSIVolumesResponse_httpStatus :: Lens' DescribeCachediSCSIVolumesResponse Int
describeCachediSCSIVolumesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCachediSCSIVolumesResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeCachediSCSIVolumesResponse' :: DescribeCachediSCSIVolumesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeCachediSCSIVolumesResponse
s@DescribeCachediSCSIVolumesResponse' {} Int
a -> DescribeCachediSCSIVolumesResponse
s {$sel:httpStatus:DescribeCachediSCSIVolumesResponse' :: Int
httpStatus = Int
a} :: DescribeCachediSCSIVolumesResponse)

instance
  Prelude.NFData
    DescribeCachediSCSIVolumesResponse
  where
  rnf :: DescribeCachediSCSIVolumesResponse -> ()
rnf DescribeCachediSCSIVolumesResponse' {Int
Maybe [CachediSCSIVolume]
httpStatus :: Int
cachediSCSIVolumes :: Maybe [CachediSCSIVolume]
$sel:httpStatus:DescribeCachediSCSIVolumesResponse' :: DescribeCachediSCSIVolumesResponse -> Int
$sel:cachediSCSIVolumes:DescribeCachediSCSIVolumesResponse' :: DescribeCachediSCSIVolumesResponse -> Maybe [CachediSCSIVolume]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CachediSCSIVolume]
cachediSCSIVolumes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus