{-# 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.ListLocalDisks
-- 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 list of the gateway\'s local disks. To specify which gateway
-- to describe, you use the Amazon Resource Name (ARN) of the gateway in
-- the body of the request.
--
-- The request returns a list of all disks, specifying which are configured
-- as working storage, cache storage, or stored volume or not configured at
-- all. The response includes a @DiskStatus@ field. This field can have a
-- value of present (the disk is available to use), missing (the disk is no
-- longer connected to the gateway), or mismatch (the disk node is occupied
-- by a disk that has incorrect metadata or the disk content is corrupted).
module Amazonka.StorageGateway.ListLocalDisks
  ( -- * Creating a Request
    ListLocalDisks (..),
    newListLocalDisks,

    -- * Request Lenses
    listLocalDisks_gatewayARN,

    -- * Destructuring the Response
    ListLocalDisksResponse (..),
    newListLocalDisksResponse,

    -- * Response Lenses
    listLocalDisksResponse_disks,
    listLocalDisksResponse_gatewayARN,
    listLocalDisksResponse_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 containing the Amazon Resource Name (ARN) of the gateway.
--
-- /See:/ 'newListLocalDisks' smart constructor.
data ListLocalDisks = ListLocalDisks'
  { ListLocalDisks -> Text
gatewayARN :: Prelude.Text
  }
  deriving (ListLocalDisks -> ListLocalDisks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLocalDisks -> ListLocalDisks -> Bool
$c/= :: ListLocalDisks -> ListLocalDisks -> Bool
== :: ListLocalDisks -> ListLocalDisks -> Bool
$c== :: ListLocalDisks -> ListLocalDisks -> Bool
Prelude.Eq, ReadPrec [ListLocalDisks]
ReadPrec ListLocalDisks
Int -> ReadS ListLocalDisks
ReadS [ListLocalDisks]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLocalDisks]
$creadListPrec :: ReadPrec [ListLocalDisks]
readPrec :: ReadPrec ListLocalDisks
$creadPrec :: ReadPrec ListLocalDisks
readList :: ReadS [ListLocalDisks]
$creadList :: ReadS [ListLocalDisks]
readsPrec :: Int -> ReadS ListLocalDisks
$creadsPrec :: Int -> ReadS ListLocalDisks
Prelude.Read, Int -> ListLocalDisks -> ShowS
[ListLocalDisks] -> ShowS
ListLocalDisks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLocalDisks] -> ShowS
$cshowList :: [ListLocalDisks] -> ShowS
show :: ListLocalDisks -> String
$cshow :: ListLocalDisks -> String
showsPrec :: Int -> ListLocalDisks -> ShowS
$cshowsPrec :: Int -> ListLocalDisks -> ShowS
Prelude.Show, forall x. Rep ListLocalDisks x -> ListLocalDisks
forall x. ListLocalDisks -> Rep ListLocalDisks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLocalDisks x -> ListLocalDisks
$cfrom :: forall x. ListLocalDisks -> Rep ListLocalDisks x
Prelude.Generic)

-- |
-- Create a value of 'ListLocalDisks' 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', 'listLocalDisks_gatewayARN' - Undocumented member.
newListLocalDisks ::
  -- | 'gatewayARN'
  Prelude.Text ->
  ListLocalDisks
newListLocalDisks :: Text -> ListLocalDisks
newListLocalDisks Text
pGatewayARN_ =
  ListLocalDisks' {$sel:gatewayARN:ListLocalDisks' :: Text
gatewayARN = Text
pGatewayARN_}

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

instance Core.AWSRequest ListLocalDisks where
  type
    AWSResponse ListLocalDisks =
      ListLocalDisksResponse
  request :: (Service -> Service) -> ListLocalDisks -> Request ListLocalDisks
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 ListLocalDisks
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListLocalDisks)))
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 [Disk] -> Maybe Text -> Int -> ListLocalDisksResponse
ListLocalDisksResponse'
            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
"Disks" 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.<*> (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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListLocalDisks where
  hashWithSalt :: Int -> ListLocalDisks -> Int
hashWithSalt Int
_salt ListLocalDisks' {Text
gatewayARN :: Text
$sel:gatewayARN:ListLocalDisks' :: ListLocalDisks -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gatewayARN

instance Prelude.NFData ListLocalDisks where
  rnf :: ListLocalDisks -> ()
rnf ListLocalDisks' {Text
gatewayARN :: Text
$sel:gatewayARN:ListLocalDisks' :: ListLocalDisks -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
gatewayARN

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

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

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

-- | /See:/ 'newListLocalDisksResponse' smart constructor.
data ListLocalDisksResponse = ListLocalDisksResponse'
  { -- | A JSON object containing the following fields:
    --
    -- -   ListLocalDisksOutput$Disks
    ListLocalDisksResponse -> Maybe [Disk]
disks :: Prelude.Maybe [Disk],
    ListLocalDisksResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListLocalDisksResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListLocalDisksResponse -> ListLocalDisksResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLocalDisksResponse -> ListLocalDisksResponse -> Bool
$c/= :: ListLocalDisksResponse -> ListLocalDisksResponse -> Bool
== :: ListLocalDisksResponse -> ListLocalDisksResponse -> Bool
$c== :: ListLocalDisksResponse -> ListLocalDisksResponse -> Bool
Prelude.Eq, ReadPrec [ListLocalDisksResponse]
ReadPrec ListLocalDisksResponse
Int -> ReadS ListLocalDisksResponse
ReadS [ListLocalDisksResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLocalDisksResponse]
$creadListPrec :: ReadPrec [ListLocalDisksResponse]
readPrec :: ReadPrec ListLocalDisksResponse
$creadPrec :: ReadPrec ListLocalDisksResponse
readList :: ReadS [ListLocalDisksResponse]
$creadList :: ReadS [ListLocalDisksResponse]
readsPrec :: Int -> ReadS ListLocalDisksResponse
$creadsPrec :: Int -> ReadS ListLocalDisksResponse
Prelude.Read, Int -> ListLocalDisksResponse -> ShowS
[ListLocalDisksResponse] -> ShowS
ListLocalDisksResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLocalDisksResponse] -> ShowS
$cshowList :: [ListLocalDisksResponse] -> ShowS
show :: ListLocalDisksResponse -> String
$cshow :: ListLocalDisksResponse -> String
showsPrec :: Int -> ListLocalDisksResponse -> ShowS
$cshowsPrec :: Int -> ListLocalDisksResponse -> ShowS
Prelude.Show, forall x. Rep ListLocalDisksResponse x -> ListLocalDisksResponse
forall x. ListLocalDisksResponse -> Rep ListLocalDisksResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLocalDisksResponse x -> ListLocalDisksResponse
$cfrom :: forall x. ListLocalDisksResponse -> Rep ListLocalDisksResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListLocalDisksResponse' 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:
--
-- 'disks', 'listLocalDisksResponse_disks' - A JSON object containing the following fields:
--
-- -   ListLocalDisksOutput$Disks
--
-- 'gatewayARN', 'listLocalDisksResponse_gatewayARN' - Undocumented member.
--
-- 'httpStatus', 'listLocalDisksResponse_httpStatus' - The response's http status code.
newListLocalDisksResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListLocalDisksResponse
newListLocalDisksResponse :: Int -> ListLocalDisksResponse
newListLocalDisksResponse Int
pHttpStatus_ =
  ListLocalDisksResponse'
    { $sel:disks:ListLocalDisksResponse' :: Maybe [Disk]
disks = forall a. Maybe a
Prelude.Nothing,
      $sel:gatewayARN:ListLocalDisksResponse' :: Maybe Text
gatewayARN = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListLocalDisksResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A JSON object containing the following fields:
--
-- -   ListLocalDisksOutput$Disks
listLocalDisksResponse_disks :: Lens.Lens' ListLocalDisksResponse (Prelude.Maybe [Disk])
listLocalDisksResponse_disks :: Lens' ListLocalDisksResponse (Maybe [Disk])
listLocalDisksResponse_disks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLocalDisksResponse' {Maybe [Disk]
disks :: Maybe [Disk]
$sel:disks:ListLocalDisksResponse' :: ListLocalDisksResponse -> Maybe [Disk]
disks} -> Maybe [Disk]
disks) (\s :: ListLocalDisksResponse
s@ListLocalDisksResponse' {} Maybe [Disk]
a -> ListLocalDisksResponse
s {$sel:disks:ListLocalDisksResponse' :: Maybe [Disk]
disks = Maybe [Disk]
a} :: ListLocalDisksResponse) 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

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

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

instance Prelude.NFData ListLocalDisksResponse where
  rnf :: ListLocalDisksResponse -> ()
rnf ListLocalDisksResponse' {Int
Maybe [Disk]
Maybe Text
httpStatus :: Int
gatewayARN :: Maybe Text
disks :: Maybe [Disk]
$sel:httpStatus:ListLocalDisksResponse' :: ListLocalDisksResponse -> Int
$sel:gatewayARN:ListLocalDisksResponse' :: ListLocalDisksResponse -> Maybe Text
$sel:disks:ListLocalDisksResponse' :: ListLocalDisksResponse -> Maybe [Disk]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Disk]
disks
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Int
httpStatus