{-# 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.AddWorkingStorage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Configures one or more gateway local disks as working storage for a
-- gateway. This operation is only supported in the stored volume gateway
-- type. This operation is deprecated in cached volume API version
-- 20120630. Use AddUploadBuffer instead.
--
-- Working storage is also referred to as upload buffer. You can also use
-- the AddUploadBuffer operation to add upload buffer to a stored volume
-- gateway.
--
-- In the request, you specify the gateway Amazon Resource Name (ARN) to
-- which you want to add working storage, and one or more disk IDs that you
-- want to configure as working storage.
module Amazonka.StorageGateway.AddWorkingStorage
  ( -- * Creating a Request
    AddWorkingStorage (..),
    newAddWorkingStorage,

    -- * Request Lenses
    addWorkingStorage_gatewayARN,
    addWorkingStorage_diskIds,

    -- * Destructuring the Response
    AddWorkingStorageResponse (..),
    newAddWorkingStorageResponse,

    -- * Response Lenses
    addWorkingStorageResponse_gatewayARN,
    addWorkingStorageResponse_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 one or more of the following fields:
--
-- -   AddWorkingStorageInput$DiskIds
--
-- /See:/ 'newAddWorkingStorage' smart constructor.
data AddWorkingStorage = AddWorkingStorage'
  { AddWorkingStorage -> Text
gatewayARN :: Prelude.Text,
    -- | An array of strings that identify disks that are to be configured as
    -- working storage. Each string has a minimum length of 1 and maximum
    -- length of 300. You can get the disk IDs from the ListLocalDisks API.
    AddWorkingStorage -> [Text]
diskIds :: [Prelude.Text]
  }
  deriving (AddWorkingStorage -> AddWorkingStorage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddWorkingStorage -> AddWorkingStorage -> Bool
$c/= :: AddWorkingStorage -> AddWorkingStorage -> Bool
== :: AddWorkingStorage -> AddWorkingStorage -> Bool
$c== :: AddWorkingStorage -> AddWorkingStorage -> Bool
Prelude.Eq, ReadPrec [AddWorkingStorage]
ReadPrec AddWorkingStorage
Int -> ReadS AddWorkingStorage
ReadS [AddWorkingStorage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddWorkingStorage]
$creadListPrec :: ReadPrec [AddWorkingStorage]
readPrec :: ReadPrec AddWorkingStorage
$creadPrec :: ReadPrec AddWorkingStorage
readList :: ReadS [AddWorkingStorage]
$creadList :: ReadS [AddWorkingStorage]
readsPrec :: Int -> ReadS AddWorkingStorage
$creadsPrec :: Int -> ReadS AddWorkingStorage
Prelude.Read, Int -> AddWorkingStorage -> ShowS
[AddWorkingStorage] -> ShowS
AddWorkingStorage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddWorkingStorage] -> ShowS
$cshowList :: [AddWorkingStorage] -> ShowS
show :: AddWorkingStorage -> String
$cshow :: AddWorkingStorage -> String
showsPrec :: Int -> AddWorkingStorage -> ShowS
$cshowsPrec :: Int -> AddWorkingStorage -> ShowS
Prelude.Show, forall x. Rep AddWorkingStorage x -> AddWorkingStorage
forall x. AddWorkingStorage -> Rep AddWorkingStorage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddWorkingStorage x -> AddWorkingStorage
$cfrom :: forall x. AddWorkingStorage -> Rep AddWorkingStorage x
Prelude.Generic)

-- |
-- Create a value of 'AddWorkingStorage' 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', 'addWorkingStorage_gatewayARN' - Undocumented member.
--
-- 'diskIds', 'addWorkingStorage_diskIds' - An array of strings that identify disks that are to be configured as
-- working storage. Each string has a minimum length of 1 and maximum
-- length of 300. You can get the disk IDs from the ListLocalDisks API.
newAddWorkingStorage ::
  -- | 'gatewayARN'
  Prelude.Text ->
  AddWorkingStorage
newAddWorkingStorage :: Text -> AddWorkingStorage
newAddWorkingStorage Text
pGatewayARN_ =
  AddWorkingStorage'
    { $sel:gatewayARN:AddWorkingStorage' :: Text
gatewayARN = Text
pGatewayARN_,
      $sel:diskIds:AddWorkingStorage' :: [Text]
diskIds = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | An array of strings that identify disks that are to be configured as
-- working storage. Each string has a minimum length of 1 and maximum
-- length of 300. You can get the disk IDs from the ListLocalDisks API.
addWorkingStorage_diskIds :: Lens.Lens' AddWorkingStorage [Prelude.Text]
addWorkingStorage_diskIds :: Lens' AddWorkingStorage [Text]
addWorkingStorage_diskIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddWorkingStorage' {[Text]
diskIds :: [Text]
$sel:diskIds:AddWorkingStorage' :: AddWorkingStorage -> [Text]
diskIds} -> [Text]
diskIds) (\s :: AddWorkingStorage
s@AddWorkingStorage' {} [Text]
a -> AddWorkingStorage
s {$sel:diskIds:AddWorkingStorage' :: [Text]
diskIds = [Text]
a} :: AddWorkingStorage) 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 AddWorkingStorage where
  type
    AWSResponse AddWorkingStorage =
      AddWorkingStorageResponse
  request :: (Service -> Service)
-> AddWorkingStorage -> Request AddWorkingStorage
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 AddWorkingStorage
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AddWorkingStorage)))
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 -> Int -> AddWorkingStorageResponse
AddWorkingStorageResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

instance Prelude.NFData AddWorkingStorage where
  rnf :: AddWorkingStorage -> ()
rnf AddWorkingStorage' {[Text]
Text
diskIds :: [Text]
gatewayARN :: Text
$sel:diskIds:AddWorkingStorage' :: AddWorkingStorage -> [Text]
$sel:gatewayARN:AddWorkingStorage' :: AddWorkingStorage -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
diskIds

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

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

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

-- | A JSON object containing the Amazon Resource Name (ARN) of the gateway
-- for which working storage was configured.
--
-- /See:/ 'newAddWorkingStorageResponse' smart constructor.
data AddWorkingStorageResponse = AddWorkingStorageResponse'
  { AddWorkingStorageResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    AddWorkingStorageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AddWorkingStorageResponse -> AddWorkingStorageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddWorkingStorageResponse -> AddWorkingStorageResponse -> Bool
$c/= :: AddWorkingStorageResponse -> AddWorkingStorageResponse -> Bool
== :: AddWorkingStorageResponse -> AddWorkingStorageResponse -> Bool
$c== :: AddWorkingStorageResponse -> AddWorkingStorageResponse -> Bool
Prelude.Eq, ReadPrec [AddWorkingStorageResponse]
ReadPrec AddWorkingStorageResponse
Int -> ReadS AddWorkingStorageResponse
ReadS [AddWorkingStorageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddWorkingStorageResponse]
$creadListPrec :: ReadPrec [AddWorkingStorageResponse]
readPrec :: ReadPrec AddWorkingStorageResponse
$creadPrec :: ReadPrec AddWorkingStorageResponse
readList :: ReadS [AddWorkingStorageResponse]
$creadList :: ReadS [AddWorkingStorageResponse]
readsPrec :: Int -> ReadS AddWorkingStorageResponse
$creadsPrec :: Int -> ReadS AddWorkingStorageResponse
Prelude.Read, Int -> AddWorkingStorageResponse -> ShowS
[AddWorkingStorageResponse] -> ShowS
AddWorkingStorageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddWorkingStorageResponse] -> ShowS
$cshowList :: [AddWorkingStorageResponse] -> ShowS
show :: AddWorkingStorageResponse -> String
$cshow :: AddWorkingStorageResponse -> String
showsPrec :: Int -> AddWorkingStorageResponse -> ShowS
$cshowsPrec :: Int -> AddWorkingStorageResponse -> ShowS
Prelude.Show, forall x.
Rep AddWorkingStorageResponse x -> AddWorkingStorageResponse
forall x.
AddWorkingStorageResponse -> Rep AddWorkingStorageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AddWorkingStorageResponse x -> AddWorkingStorageResponse
$cfrom :: forall x.
AddWorkingStorageResponse -> Rep AddWorkingStorageResponse x
Prelude.Generic)

-- |
-- Create a value of 'AddWorkingStorageResponse' 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', 'addWorkingStorageResponse_gatewayARN' - Undocumented member.
--
-- 'httpStatus', 'addWorkingStorageResponse_httpStatus' - The response's http status code.
newAddWorkingStorageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AddWorkingStorageResponse
newAddWorkingStorageResponse :: Int -> AddWorkingStorageResponse
newAddWorkingStorageResponse Int
pHttpStatus_ =
  AddWorkingStorageResponse'
    { $sel:gatewayARN:AddWorkingStorageResponse' :: Maybe Text
gatewayARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AddWorkingStorageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData AddWorkingStorageResponse where
  rnf :: AddWorkingStorageResponse -> ()
rnf AddWorkingStorageResponse' {Int
Maybe Text
httpStatus :: Int
gatewayARN :: Maybe Text
$sel:httpStatus:AddWorkingStorageResponse' :: AddWorkingStorageResponse -> Int
$sel:gatewayARN:AddWorkingStorageResponse' :: AddWorkingStorageResponse -> 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 Int
httpStatus