{-# 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.AddCache
-- 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 cache for a gateway. This
-- operation is only supported in the cached volume, tape, and file gateway
-- type (see
-- <https://docs.aws.amazon.com/storagegateway/latest/userguide/StorageGatewayConcepts.html How Storage Gateway works (architecture)>.
--
-- In the request, you specify the gateway Amazon Resource Name (ARN) to
-- which you want to add cache, and one or more disk IDs that you want to
-- configure as cache.
module Amazonka.StorageGateway.AddCache
  ( -- * Creating a Request
    AddCache (..),
    newAddCache,

    -- * Request Lenses
    addCache_gatewayARN,
    addCache_diskIds,

    -- * Destructuring the Response
    AddCacheResponse (..),
    newAddCacheResponse,

    -- * Response Lenses
    addCacheResponse_gatewayARN,
    addCacheResponse_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:/ 'newAddCache' smart constructor.
data AddCache = AddCache'
  { AddCache -> 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.
    AddCache -> [Text]
diskIds :: [Prelude.Text]
  }
  deriving (AddCache -> AddCache -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddCache -> AddCache -> Bool
$c/= :: AddCache -> AddCache -> Bool
== :: AddCache -> AddCache -> Bool
$c== :: AddCache -> AddCache -> Bool
Prelude.Eq, ReadPrec [AddCache]
ReadPrec AddCache
Int -> ReadS AddCache
ReadS [AddCache]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddCache]
$creadListPrec :: ReadPrec [AddCache]
readPrec :: ReadPrec AddCache
$creadPrec :: ReadPrec AddCache
readList :: ReadS [AddCache]
$creadList :: ReadS [AddCache]
readsPrec :: Int -> ReadS AddCache
$creadsPrec :: Int -> ReadS AddCache
Prelude.Read, Int -> AddCache -> ShowS
[AddCache] -> ShowS
AddCache -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddCache] -> ShowS
$cshowList :: [AddCache] -> ShowS
show :: AddCache -> String
$cshow :: AddCache -> String
showsPrec :: Int -> AddCache -> ShowS
$cshowsPrec :: Int -> AddCache -> ShowS
Prelude.Show, forall x. Rep AddCache x -> AddCache
forall x. AddCache -> Rep AddCache x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddCache x -> AddCache
$cfrom :: forall x. AddCache -> Rep AddCache x
Prelude.Generic)

-- |
-- Create a value of 'AddCache' 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', 'addCache_gatewayARN' - Undocumented member.
--
-- 'diskIds', 'addCache_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.
newAddCache ::
  -- | 'gatewayARN'
  Prelude.Text ->
  AddCache
newAddCache :: Text -> AddCache
newAddCache Text
pGatewayARN_ =
  AddCache'
    { $sel:gatewayARN:AddCache' :: Text
gatewayARN = Text
pGatewayARN_,
      $sel:diskIds:AddCache' :: [Text]
diskIds = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | 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.
addCache_diskIds :: Lens.Lens' AddCache [Prelude.Text]
addCache_diskIds :: Lens' AddCache [Text]
addCache_diskIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddCache' {[Text]
diskIds :: [Text]
$sel:diskIds:AddCache' :: AddCache -> [Text]
diskIds} -> [Text]
diskIds) (\s :: AddCache
s@AddCache' {} [Text]
a -> AddCache
s {$sel:diskIds:AddCache' :: [Text]
diskIds = [Text]
a} :: AddCache) 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 AddCache where
  type AWSResponse AddCache = AddCacheResponse
  request :: (Service -> Service) -> AddCache -> Request AddCache
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 AddCache
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AddCache)))
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 -> AddCacheResponse
AddCacheResponse'
            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 AddCache where
  hashWithSalt :: Int -> AddCache -> Int
hashWithSalt Int
_salt AddCache' {[Text]
Text
diskIds :: [Text]
gatewayARN :: Text
$sel:diskIds:AddCache' :: AddCache -> [Text]
$sel:gatewayARN:AddCache' :: AddCache -> 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 AddCache where
  rnf :: AddCache -> ()
rnf AddCache' {[Text]
Text
diskIds :: [Text]
gatewayARN :: Text
$sel:diskIds:AddCache' :: AddCache -> [Text]
$sel:gatewayARN:AddCache' :: AddCache -> 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 AddCache where
  toHeaders :: AddCache -> 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.AddCache" ::
                          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 AddCache where
  toJSON :: AddCache -> Value
toJSON AddCache' {[Text]
Text
diskIds :: [Text]
gatewayARN :: Text
$sel:diskIds:AddCache' :: AddCache -> [Text]
$sel:gatewayARN:AddCache' :: AddCache -> 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 AddCache where
  toPath :: AddCache -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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

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