{-# 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.Macie.UpdateS3Resources
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- (Discontinued) Updates the classification types for the specified S3
-- resources. If @memberAccountId@ isn\'t specified, the action updates the
-- classification types of the S3 resources associated with Amazon Macie
-- Classic for the current Macie Classic administrator account. If
-- @memberAccountId@ is specified, the action updates the classification
-- types of the S3 resources associated with Macie Classic for the
-- specified member account.
module Amazonka.Macie.UpdateS3Resources
  ( -- * Creating a Request
    UpdateS3Resources (..),
    newUpdateS3Resources,

    -- * Request Lenses
    updateS3Resources_memberAccountId,
    updateS3Resources_s3ResourcesUpdate,

    -- * Destructuring the Response
    UpdateS3ResourcesResponse (..),
    newUpdateS3ResourcesResponse,

    -- * Response Lenses
    updateS3ResourcesResponse_failedS3Resources,
    updateS3ResourcesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateS3Resources' smart constructor.
data UpdateS3Resources = UpdateS3Resources'
  { -- | (Discontinued) The Amazon Web Services account ID of the Amazon Macie
    -- Classic member account whose S3 resources\' classification types you
    -- want to update.
    UpdateS3Resources -> Maybe Text
memberAccountId :: Prelude.Maybe Prelude.Text,
    -- | (Discontinued) The S3 resources whose classification types you want to
    -- update.
    UpdateS3Resources -> [S3ResourceClassificationUpdate]
s3ResourcesUpdate :: [S3ResourceClassificationUpdate]
  }
  deriving (UpdateS3Resources -> UpdateS3Resources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateS3Resources -> UpdateS3Resources -> Bool
$c/= :: UpdateS3Resources -> UpdateS3Resources -> Bool
== :: UpdateS3Resources -> UpdateS3Resources -> Bool
$c== :: UpdateS3Resources -> UpdateS3Resources -> Bool
Prelude.Eq, ReadPrec [UpdateS3Resources]
ReadPrec UpdateS3Resources
Int -> ReadS UpdateS3Resources
ReadS [UpdateS3Resources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateS3Resources]
$creadListPrec :: ReadPrec [UpdateS3Resources]
readPrec :: ReadPrec UpdateS3Resources
$creadPrec :: ReadPrec UpdateS3Resources
readList :: ReadS [UpdateS3Resources]
$creadList :: ReadS [UpdateS3Resources]
readsPrec :: Int -> ReadS UpdateS3Resources
$creadsPrec :: Int -> ReadS UpdateS3Resources
Prelude.Read, Int -> UpdateS3Resources -> ShowS
[UpdateS3Resources] -> ShowS
UpdateS3Resources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateS3Resources] -> ShowS
$cshowList :: [UpdateS3Resources] -> ShowS
show :: UpdateS3Resources -> String
$cshow :: UpdateS3Resources -> String
showsPrec :: Int -> UpdateS3Resources -> ShowS
$cshowsPrec :: Int -> UpdateS3Resources -> ShowS
Prelude.Show, forall x. Rep UpdateS3Resources x -> UpdateS3Resources
forall x. UpdateS3Resources -> Rep UpdateS3Resources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateS3Resources x -> UpdateS3Resources
$cfrom :: forall x. UpdateS3Resources -> Rep UpdateS3Resources x
Prelude.Generic)

-- |
-- Create a value of 'UpdateS3Resources' 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:
--
-- 'memberAccountId', 'updateS3Resources_memberAccountId' - (Discontinued) The Amazon Web Services account ID of the Amazon Macie
-- Classic member account whose S3 resources\' classification types you
-- want to update.
--
-- 's3ResourcesUpdate', 'updateS3Resources_s3ResourcesUpdate' - (Discontinued) The S3 resources whose classification types you want to
-- update.
newUpdateS3Resources ::
  UpdateS3Resources
newUpdateS3Resources :: UpdateS3Resources
newUpdateS3Resources =
  UpdateS3Resources'
    { $sel:memberAccountId:UpdateS3Resources' :: Maybe Text
memberAccountId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:s3ResourcesUpdate:UpdateS3Resources' :: [S3ResourceClassificationUpdate]
s3ResourcesUpdate = forall a. Monoid a => a
Prelude.mempty
    }

-- | (Discontinued) The Amazon Web Services account ID of the Amazon Macie
-- Classic member account whose S3 resources\' classification types you
-- want to update.
updateS3Resources_memberAccountId :: Lens.Lens' UpdateS3Resources (Prelude.Maybe Prelude.Text)
updateS3Resources_memberAccountId :: Lens' UpdateS3Resources (Maybe Text)
updateS3Resources_memberAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateS3Resources' {Maybe Text
memberAccountId :: Maybe Text
$sel:memberAccountId:UpdateS3Resources' :: UpdateS3Resources -> Maybe Text
memberAccountId} -> Maybe Text
memberAccountId) (\s :: UpdateS3Resources
s@UpdateS3Resources' {} Maybe Text
a -> UpdateS3Resources
s {$sel:memberAccountId:UpdateS3Resources' :: Maybe Text
memberAccountId = Maybe Text
a} :: UpdateS3Resources)

-- | (Discontinued) The S3 resources whose classification types you want to
-- update.
updateS3Resources_s3ResourcesUpdate :: Lens.Lens' UpdateS3Resources [S3ResourceClassificationUpdate]
updateS3Resources_s3ResourcesUpdate :: Lens' UpdateS3Resources [S3ResourceClassificationUpdate]
updateS3Resources_s3ResourcesUpdate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateS3Resources' {[S3ResourceClassificationUpdate]
s3ResourcesUpdate :: [S3ResourceClassificationUpdate]
$sel:s3ResourcesUpdate:UpdateS3Resources' :: UpdateS3Resources -> [S3ResourceClassificationUpdate]
s3ResourcesUpdate} -> [S3ResourceClassificationUpdate]
s3ResourcesUpdate) (\s :: UpdateS3Resources
s@UpdateS3Resources' {} [S3ResourceClassificationUpdate]
a -> UpdateS3Resources
s {$sel:s3ResourcesUpdate:UpdateS3Resources' :: [S3ResourceClassificationUpdate]
s3ResourcesUpdate = [S3ResourceClassificationUpdate]
a} :: UpdateS3Resources) 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 UpdateS3Resources where
  type
    AWSResponse UpdateS3Resources =
      UpdateS3ResourcesResponse
  request :: (Service -> Service)
-> UpdateS3Resources -> Request UpdateS3Resources
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 UpdateS3Resources
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateS3Resources)))
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 [FailedS3Resource] -> Int -> UpdateS3ResourcesResponse
UpdateS3ResourcesResponse'
            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
"failedS3Resources"
                            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 UpdateS3Resources where
  hashWithSalt :: Int -> UpdateS3Resources -> Int
hashWithSalt Int
_salt UpdateS3Resources' {[S3ResourceClassificationUpdate]
Maybe Text
s3ResourcesUpdate :: [S3ResourceClassificationUpdate]
memberAccountId :: Maybe Text
$sel:s3ResourcesUpdate:UpdateS3Resources' :: UpdateS3Resources -> [S3ResourceClassificationUpdate]
$sel:memberAccountId:UpdateS3Resources' :: UpdateS3Resources -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
memberAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [S3ResourceClassificationUpdate]
s3ResourcesUpdate

instance Prelude.NFData UpdateS3Resources where
  rnf :: UpdateS3Resources -> ()
rnf UpdateS3Resources' {[S3ResourceClassificationUpdate]
Maybe Text
s3ResourcesUpdate :: [S3ResourceClassificationUpdate]
memberAccountId :: Maybe Text
$sel:s3ResourcesUpdate:UpdateS3Resources' :: UpdateS3Resources -> [S3ResourceClassificationUpdate]
$sel:memberAccountId:UpdateS3Resources' :: UpdateS3Resources -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
memberAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [S3ResourceClassificationUpdate]
s3ResourcesUpdate

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

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

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

-- | /See:/ 'newUpdateS3ResourcesResponse' smart constructor.
data UpdateS3ResourcesResponse = UpdateS3ResourcesResponse'
  { -- | (Discontinued) The S3 resources whose classification types can\'t be
    -- updated. An error code and an error message are provided for each failed
    -- item.
    UpdateS3ResourcesResponse -> Maybe [FailedS3Resource]
failedS3Resources :: Prelude.Maybe [FailedS3Resource],
    -- | The response's http status code.
    UpdateS3ResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateS3ResourcesResponse -> UpdateS3ResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateS3ResourcesResponse -> UpdateS3ResourcesResponse -> Bool
$c/= :: UpdateS3ResourcesResponse -> UpdateS3ResourcesResponse -> Bool
== :: UpdateS3ResourcesResponse -> UpdateS3ResourcesResponse -> Bool
$c== :: UpdateS3ResourcesResponse -> UpdateS3ResourcesResponse -> Bool
Prelude.Eq, ReadPrec [UpdateS3ResourcesResponse]
ReadPrec UpdateS3ResourcesResponse
Int -> ReadS UpdateS3ResourcesResponse
ReadS [UpdateS3ResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateS3ResourcesResponse]
$creadListPrec :: ReadPrec [UpdateS3ResourcesResponse]
readPrec :: ReadPrec UpdateS3ResourcesResponse
$creadPrec :: ReadPrec UpdateS3ResourcesResponse
readList :: ReadS [UpdateS3ResourcesResponse]
$creadList :: ReadS [UpdateS3ResourcesResponse]
readsPrec :: Int -> ReadS UpdateS3ResourcesResponse
$creadsPrec :: Int -> ReadS UpdateS3ResourcesResponse
Prelude.Read, Int -> UpdateS3ResourcesResponse -> ShowS
[UpdateS3ResourcesResponse] -> ShowS
UpdateS3ResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateS3ResourcesResponse] -> ShowS
$cshowList :: [UpdateS3ResourcesResponse] -> ShowS
show :: UpdateS3ResourcesResponse -> String
$cshow :: UpdateS3ResourcesResponse -> String
showsPrec :: Int -> UpdateS3ResourcesResponse -> ShowS
$cshowsPrec :: Int -> UpdateS3ResourcesResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateS3ResourcesResponse x -> UpdateS3ResourcesResponse
forall x.
UpdateS3ResourcesResponse -> Rep UpdateS3ResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateS3ResourcesResponse x -> UpdateS3ResourcesResponse
$cfrom :: forall x.
UpdateS3ResourcesResponse -> Rep UpdateS3ResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateS3ResourcesResponse' 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:
--
-- 'failedS3Resources', 'updateS3ResourcesResponse_failedS3Resources' - (Discontinued) The S3 resources whose classification types can\'t be
-- updated. An error code and an error message are provided for each failed
-- item.
--
-- 'httpStatus', 'updateS3ResourcesResponse_httpStatus' - The response's http status code.
newUpdateS3ResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateS3ResourcesResponse
newUpdateS3ResourcesResponse :: Int -> UpdateS3ResourcesResponse
newUpdateS3ResourcesResponse Int
pHttpStatus_ =
  UpdateS3ResourcesResponse'
    { $sel:failedS3Resources:UpdateS3ResourcesResponse' :: Maybe [FailedS3Resource]
failedS3Resources =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateS3ResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | (Discontinued) The S3 resources whose classification types can\'t be
-- updated. An error code and an error message are provided for each failed
-- item.
updateS3ResourcesResponse_failedS3Resources :: Lens.Lens' UpdateS3ResourcesResponse (Prelude.Maybe [FailedS3Resource])
updateS3ResourcesResponse_failedS3Resources :: Lens' UpdateS3ResourcesResponse (Maybe [FailedS3Resource])
updateS3ResourcesResponse_failedS3Resources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateS3ResourcesResponse' {Maybe [FailedS3Resource]
failedS3Resources :: Maybe [FailedS3Resource]
$sel:failedS3Resources:UpdateS3ResourcesResponse' :: UpdateS3ResourcesResponse -> Maybe [FailedS3Resource]
failedS3Resources} -> Maybe [FailedS3Resource]
failedS3Resources) (\s :: UpdateS3ResourcesResponse
s@UpdateS3ResourcesResponse' {} Maybe [FailedS3Resource]
a -> UpdateS3ResourcesResponse
s {$sel:failedS3Resources:UpdateS3ResourcesResponse' :: Maybe [FailedS3Resource]
failedS3Resources = Maybe [FailedS3Resource]
a} :: UpdateS3ResourcesResponse) 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.
updateS3ResourcesResponse_httpStatus :: Lens.Lens' UpdateS3ResourcesResponse Prelude.Int
updateS3ResourcesResponse_httpStatus :: Lens' UpdateS3ResourcesResponse Int
updateS3ResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateS3ResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateS3ResourcesResponse' :: UpdateS3ResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateS3ResourcesResponse
s@UpdateS3ResourcesResponse' {} Int
a -> UpdateS3ResourcesResponse
s {$sel:httpStatus:UpdateS3ResourcesResponse' :: Int
httpStatus = Int
a} :: UpdateS3ResourcesResponse)

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