{-# 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.MemoryDb.BatchUpdateCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Apply the service update to a list of clusters supplied. For more
-- information on service updates and applying them, see
-- <https://docs.aws.amazon.com/MemoryDB/latest/devguide/managing-updates.html#applying-updates Applying the service updates>.
module Amazonka.MemoryDb.BatchUpdateCluster
  ( -- * Creating a Request
    BatchUpdateCluster (..),
    newBatchUpdateCluster,

    -- * Request Lenses
    batchUpdateCluster_serviceUpdate,
    batchUpdateCluster_clusterNames,

    -- * Destructuring the Response
    BatchUpdateClusterResponse (..),
    newBatchUpdateClusterResponse,

    -- * Response Lenses
    batchUpdateClusterResponse_processedClusters,
    batchUpdateClusterResponse_unprocessedClusters,
    batchUpdateClusterResponse_httpStatus,
  )
where

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

-- | /See:/ 'newBatchUpdateCluster' smart constructor.
data BatchUpdateCluster = BatchUpdateCluster'
  { -- | The unique ID of the service update
    BatchUpdateCluster -> Maybe ServiceUpdateRequest
serviceUpdate :: Prelude.Maybe ServiceUpdateRequest,
    -- | The cluster names to apply the updates.
    BatchUpdateCluster -> [Text]
clusterNames :: [Prelude.Text]
  }
  deriving (BatchUpdateCluster -> BatchUpdateCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchUpdateCluster -> BatchUpdateCluster -> Bool
$c/= :: BatchUpdateCluster -> BatchUpdateCluster -> Bool
== :: BatchUpdateCluster -> BatchUpdateCluster -> Bool
$c== :: BatchUpdateCluster -> BatchUpdateCluster -> Bool
Prelude.Eq, ReadPrec [BatchUpdateCluster]
ReadPrec BatchUpdateCluster
Int -> ReadS BatchUpdateCluster
ReadS [BatchUpdateCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchUpdateCluster]
$creadListPrec :: ReadPrec [BatchUpdateCluster]
readPrec :: ReadPrec BatchUpdateCluster
$creadPrec :: ReadPrec BatchUpdateCluster
readList :: ReadS [BatchUpdateCluster]
$creadList :: ReadS [BatchUpdateCluster]
readsPrec :: Int -> ReadS BatchUpdateCluster
$creadsPrec :: Int -> ReadS BatchUpdateCluster
Prelude.Read, Int -> BatchUpdateCluster -> ShowS
[BatchUpdateCluster] -> ShowS
BatchUpdateCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchUpdateCluster] -> ShowS
$cshowList :: [BatchUpdateCluster] -> ShowS
show :: BatchUpdateCluster -> String
$cshow :: BatchUpdateCluster -> String
showsPrec :: Int -> BatchUpdateCluster -> ShowS
$cshowsPrec :: Int -> BatchUpdateCluster -> ShowS
Prelude.Show, forall x. Rep BatchUpdateCluster x -> BatchUpdateCluster
forall x. BatchUpdateCluster -> Rep BatchUpdateCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchUpdateCluster x -> BatchUpdateCluster
$cfrom :: forall x. BatchUpdateCluster -> Rep BatchUpdateCluster x
Prelude.Generic)

-- |
-- Create a value of 'BatchUpdateCluster' 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:
--
-- 'serviceUpdate', 'batchUpdateCluster_serviceUpdate' - The unique ID of the service update
--
-- 'clusterNames', 'batchUpdateCluster_clusterNames' - The cluster names to apply the updates.
newBatchUpdateCluster ::
  BatchUpdateCluster
newBatchUpdateCluster :: BatchUpdateCluster
newBatchUpdateCluster =
  BatchUpdateCluster'
    { $sel:serviceUpdate:BatchUpdateCluster' :: Maybe ServiceUpdateRequest
serviceUpdate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clusterNames:BatchUpdateCluster' :: [Text]
clusterNames = forall a. Monoid a => a
Prelude.mempty
    }

-- | The unique ID of the service update
batchUpdateCluster_serviceUpdate :: Lens.Lens' BatchUpdateCluster (Prelude.Maybe ServiceUpdateRequest)
batchUpdateCluster_serviceUpdate :: Lens' BatchUpdateCluster (Maybe ServiceUpdateRequest)
batchUpdateCluster_serviceUpdate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchUpdateCluster' {Maybe ServiceUpdateRequest
serviceUpdate :: Maybe ServiceUpdateRequest
$sel:serviceUpdate:BatchUpdateCluster' :: BatchUpdateCluster -> Maybe ServiceUpdateRequest
serviceUpdate} -> Maybe ServiceUpdateRequest
serviceUpdate) (\s :: BatchUpdateCluster
s@BatchUpdateCluster' {} Maybe ServiceUpdateRequest
a -> BatchUpdateCluster
s {$sel:serviceUpdate:BatchUpdateCluster' :: Maybe ServiceUpdateRequest
serviceUpdate = Maybe ServiceUpdateRequest
a} :: BatchUpdateCluster)

-- | The cluster names to apply the updates.
batchUpdateCluster_clusterNames :: Lens.Lens' BatchUpdateCluster [Prelude.Text]
batchUpdateCluster_clusterNames :: Lens' BatchUpdateCluster [Text]
batchUpdateCluster_clusterNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchUpdateCluster' {[Text]
clusterNames :: [Text]
$sel:clusterNames:BatchUpdateCluster' :: BatchUpdateCluster -> [Text]
clusterNames} -> [Text]
clusterNames) (\s :: BatchUpdateCluster
s@BatchUpdateCluster' {} [Text]
a -> BatchUpdateCluster
s {$sel:clusterNames:BatchUpdateCluster' :: [Text]
clusterNames = [Text]
a} :: BatchUpdateCluster) 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 BatchUpdateCluster where
  type
    AWSResponse BatchUpdateCluster =
      BatchUpdateClusterResponse
  request :: (Service -> Service)
-> BatchUpdateCluster -> Request BatchUpdateCluster
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 BatchUpdateCluster
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchUpdateCluster)))
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 [Cluster]
-> Maybe [UnprocessedCluster] -> Int -> BatchUpdateClusterResponse
BatchUpdateClusterResponse'
            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
"ProcessedClusters"
                            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
"UnprocessedClusters"
                            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 BatchUpdateCluster where
  hashWithSalt :: Int -> BatchUpdateCluster -> Int
hashWithSalt Int
_salt BatchUpdateCluster' {[Text]
Maybe ServiceUpdateRequest
clusterNames :: [Text]
serviceUpdate :: Maybe ServiceUpdateRequest
$sel:clusterNames:BatchUpdateCluster' :: BatchUpdateCluster -> [Text]
$sel:serviceUpdate:BatchUpdateCluster' :: BatchUpdateCluster -> Maybe ServiceUpdateRequest
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServiceUpdateRequest
serviceUpdate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
clusterNames

instance Prelude.NFData BatchUpdateCluster where
  rnf :: BatchUpdateCluster -> ()
rnf BatchUpdateCluster' {[Text]
Maybe ServiceUpdateRequest
clusterNames :: [Text]
serviceUpdate :: Maybe ServiceUpdateRequest
$sel:clusterNames:BatchUpdateCluster' :: BatchUpdateCluster -> [Text]
$sel:serviceUpdate:BatchUpdateCluster' :: BatchUpdateCluster -> Maybe ServiceUpdateRequest
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ServiceUpdateRequest
serviceUpdate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
clusterNames

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

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

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

-- | /See:/ 'newBatchUpdateClusterResponse' smart constructor.
data BatchUpdateClusterResponse = BatchUpdateClusterResponse'
  { -- | The list of clusters that have been updated.
    BatchUpdateClusterResponse -> Maybe [Cluster]
processedClusters :: Prelude.Maybe [Cluster],
    -- | The list of clusters where updates have not been applied.
    BatchUpdateClusterResponse -> Maybe [UnprocessedCluster]
unprocessedClusters :: Prelude.Maybe [UnprocessedCluster],
    -- | The response's http status code.
    BatchUpdateClusterResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchUpdateClusterResponse -> BatchUpdateClusterResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchUpdateClusterResponse -> BatchUpdateClusterResponse -> Bool
$c/= :: BatchUpdateClusterResponse -> BatchUpdateClusterResponse -> Bool
== :: BatchUpdateClusterResponse -> BatchUpdateClusterResponse -> Bool
$c== :: BatchUpdateClusterResponse -> BatchUpdateClusterResponse -> Bool
Prelude.Eq, ReadPrec [BatchUpdateClusterResponse]
ReadPrec BatchUpdateClusterResponse
Int -> ReadS BatchUpdateClusterResponse
ReadS [BatchUpdateClusterResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchUpdateClusterResponse]
$creadListPrec :: ReadPrec [BatchUpdateClusterResponse]
readPrec :: ReadPrec BatchUpdateClusterResponse
$creadPrec :: ReadPrec BatchUpdateClusterResponse
readList :: ReadS [BatchUpdateClusterResponse]
$creadList :: ReadS [BatchUpdateClusterResponse]
readsPrec :: Int -> ReadS BatchUpdateClusterResponse
$creadsPrec :: Int -> ReadS BatchUpdateClusterResponse
Prelude.Read, Int -> BatchUpdateClusterResponse -> ShowS
[BatchUpdateClusterResponse] -> ShowS
BatchUpdateClusterResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchUpdateClusterResponse] -> ShowS
$cshowList :: [BatchUpdateClusterResponse] -> ShowS
show :: BatchUpdateClusterResponse -> String
$cshow :: BatchUpdateClusterResponse -> String
showsPrec :: Int -> BatchUpdateClusterResponse -> ShowS
$cshowsPrec :: Int -> BatchUpdateClusterResponse -> ShowS
Prelude.Show, forall x.
Rep BatchUpdateClusterResponse x -> BatchUpdateClusterResponse
forall x.
BatchUpdateClusterResponse -> Rep BatchUpdateClusterResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchUpdateClusterResponse x -> BatchUpdateClusterResponse
$cfrom :: forall x.
BatchUpdateClusterResponse -> Rep BatchUpdateClusterResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchUpdateClusterResponse' 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:
--
-- 'processedClusters', 'batchUpdateClusterResponse_processedClusters' - The list of clusters that have been updated.
--
-- 'unprocessedClusters', 'batchUpdateClusterResponse_unprocessedClusters' - The list of clusters where updates have not been applied.
--
-- 'httpStatus', 'batchUpdateClusterResponse_httpStatus' - The response's http status code.
newBatchUpdateClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchUpdateClusterResponse
newBatchUpdateClusterResponse :: Int -> BatchUpdateClusterResponse
newBatchUpdateClusterResponse Int
pHttpStatus_ =
  BatchUpdateClusterResponse'
    { $sel:processedClusters:BatchUpdateClusterResponse' :: Maybe [Cluster]
processedClusters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:unprocessedClusters:BatchUpdateClusterResponse' :: Maybe [UnprocessedCluster]
unprocessedClusters = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchUpdateClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of clusters that have been updated.
batchUpdateClusterResponse_processedClusters :: Lens.Lens' BatchUpdateClusterResponse (Prelude.Maybe [Cluster])
batchUpdateClusterResponse_processedClusters :: Lens' BatchUpdateClusterResponse (Maybe [Cluster])
batchUpdateClusterResponse_processedClusters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchUpdateClusterResponse' {Maybe [Cluster]
processedClusters :: Maybe [Cluster]
$sel:processedClusters:BatchUpdateClusterResponse' :: BatchUpdateClusterResponse -> Maybe [Cluster]
processedClusters} -> Maybe [Cluster]
processedClusters) (\s :: BatchUpdateClusterResponse
s@BatchUpdateClusterResponse' {} Maybe [Cluster]
a -> BatchUpdateClusterResponse
s {$sel:processedClusters:BatchUpdateClusterResponse' :: Maybe [Cluster]
processedClusters = Maybe [Cluster]
a} :: BatchUpdateClusterResponse) 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 list of clusters where updates have not been applied.
batchUpdateClusterResponse_unprocessedClusters :: Lens.Lens' BatchUpdateClusterResponse (Prelude.Maybe [UnprocessedCluster])
batchUpdateClusterResponse_unprocessedClusters :: Lens' BatchUpdateClusterResponse (Maybe [UnprocessedCluster])
batchUpdateClusterResponse_unprocessedClusters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchUpdateClusterResponse' {Maybe [UnprocessedCluster]
unprocessedClusters :: Maybe [UnprocessedCluster]
$sel:unprocessedClusters:BatchUpdateClusterResponse' :: BatchUpdateClusterResponse -> Maybe [UnprocessedCluster]
unprocessedClusters} -> Maybe [UnprocessedCluster]
unprocessedClusters) (\s :: BatchUpdateClusterResponse
s@BatchUpdateClusterResponse' {} Maybe [UnprocessedCluster]
a -> BatchUpdateClusterResponse
s {$sel:unprocessedClusters:BatchUpdateClusterResponse' :: Maybe [UnprocessedCluster]
unprocessedClusters = Maybe [UnprocessedCluster]
a} :: BatchUpdateClusterResponse) 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.
batchUpdateClusterResponse_httpStatus :: Lens.Lens' BatchUpdateClusterResponse Prelude.Int
batchUpdateClusterResponse_httpStatus :: Lens' BatchUpdateClusterResponse Int
batchUpdateClusterResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchUpdateClusterResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchUpdateClusterResponse' :: BatchUpdateClusterResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchUpdateClusterResponse
s@BatchUpdateClusterResponse' {} Int
a -> BatchUpdateClusterResponse
s {$sel:httpStatus:BatchUpdateClusterResponse' :: Int
httpStatus = Int
a} :: BatchUpdateClusterResponse)

instance Prelude.NFData BatchUpdateClusterResponse where
  rnf :: BatchUpdateClusterResponse -> ()
rnf BatchUpdateClusterResponse' {Int
Maybe [Cluster]
Maybe [UnprocessedCluster]
httpStatus :: Int
unprocessedClusters :: Maybe [UnprocessedCluster]
processedClusters :: Maybe [Cluster]
$sel:httpStatus:BatchUpdateClusterResponse' :: BatchUpdateClusterResponse -> Int
$sel:unprocessedClusters:BatchUpdateClusterResponse' :: BatchUpdateClusterResponse -> Maybe [UnprocessedCluster]
$sel:processedClusters:BatchUpdateClusterResponse' :: BatchUpdateClusterResponse -> Maybe [Cluster]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Cluster]
processedClusters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [UnprocessedCluster]
unprocessedClusters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus