{-# 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.MacieV2.UpdateRevealConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the status and configuration settings for retrieving occurrences
-- of sensitive data reported by findings.
module Amazonka.MacieV2.UpdateRevealConfiguration
  ( -- * Creating a Request
    UpdateRevealConfiguration (..),
    newUpdateRevealConfiguration,

    -- * Request Lenses
    updateRevealConfiguration_configuration,

    -- * Destructuring the Response
    UpdateRevealConfigurationResponse (..),
    newUpdateRevealConfigurationResponse,

    -- * Response Lenses
    updateRevealConfigurationResponse_configuration,
    updateRevealConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateRevealConfiguration' smart constructor.
data UpdateRevealConfiguration = UpdateRevealConfiguration'
  { -- | The new configuration settings and the status of the configuration for
    -- the account.
    UpdateRevealConfiguration -> RevealConfiguration
configuration :: RevealConfiguration
  }
  deriving (UpdateRevealConfiguration -> UpdateRevealConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRevealConfiguration -> UpdateRevealConfiguration -> Bool
$c/= :: UpdateRevealConfiguration -> UpdateRevealConfiguration -> Bool
== :: UpdateRevealConfiguration -> UpdateRevealConfiguration -> Bool
$c== :: UpdateRevealConfiguration -> UpdateRevealConfiguration -> Bool
Prelude.Eq, ReadPrec [UpdateRevealConfiguration]
ReadPrec UpdateRevealConfiguration
Int -> ReadS UpdateRevealConfiguration
ReadS [UpdateRevealConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRevealConfiguration]
$creadListPrec :: ReadPrec [UpdateRevealConfiguration]
readPrec :: ReadPrec UpdateRevealConfiguration
$creadPrec :: ReadPrec UpdateRevealConfiguration
readList :: ReadS [UpdateRevealConfiguration]
$creadList :: ReadS [UpdateRevealConfiguration]
readsPrec :: Int -> ReadS UpdateRevealConfiguration
$creadsPrec :: Int -> ReadS UpdateRevealConfiguration
Prelude.Read, Int -> UpdateRevealConfiguration -> ShowS
[UpdateRevealConfiguration] -> ShowS
UpdateRevealConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRevealConfiguration] -> ShowS
$cshowList :: [UpdateRevealConfiguration] -> ShowS
show :: UpdateRevealConfiguration -> String
$cshow :: UpdateRevealConfiguration -> String
showsPrec :: Int -> UpdateRevealConfiguration -> ShowS
$cshowsPrec :: Int -> UpdateRevealConfiguration -> ShowS
Prelude.Show, forall x.
Rep UpdateRevealConfiguration x -> UpdateRevealConfiguration
forall x.
UpdateRevealConfiguration -> Rep UpdateRevealConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateRevealConfiguration x -> UpdateRevealConfiguration
$cfrom :: forall x.
UpdateRevealConfiguration -> Rep UpdateRevealConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRevealConfiguration' 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:
--
-- 'configuration', 'updateRevealConfiguration_configuration' - The new configuration settings and the status of the configuration for
-- the account.
newUpdateRevealConfiguration ::
  -- | 'configuration'
  RevealConfiguration ->
  UpdateRevealConfiguration
newUpdateRevealConfiguration :: RevealConfiguration -> UpdateRevealConfiguration
newUpdateRevealConfiguration RevealConfiguration
pConfiguration_ =
  UpdateRevealConfiguration'
    { $sel:configuration:UpdateRevealConfiguration' :: RevealConfiguration
configuration =
        RevealConfiguration
pConfiguration_
    }

-- | The new configuration settings and the status of the configuration for
-- the account.
updateRevealConfiguration_configuration :: Lens.Lens' UpdateRevealConfiguration RevealConfiguration
updateRevealConfiguration_configuration :: Lens' UpdateRevealConfiguration RevealConfiguration
updateRevealConfiguration_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevealConfiguration' {RevealConfiguration
configuration :: RevealConfiguration
$sel:configuration:UpdateRevealConfiguration' :: UpdateRevealConfiguration -> RevealConfiguration
configuration} -> RevealConfiguration
configuration) (\s :: UpdateRevealConfiguration
s@UpdateRevealConfiguration' {} RevealConfiguration
a -> UpdateRevealConfiguration
s {$sel:configuration:UpdateRevealConfiguration' :: RevealConfiguration
configuration = RevealConfiguration
a} :: UpdateRevealConfiguration)

instance Core.AWSRequest UpdateRevealConfiguration where
  type
    AWSResponse UpdateRevealConfiguration =
      UpdateRevealConfigurationResponse
  request :: (Service -> Service)
-> UpdateRevealConfiguration -> Request UpdateRevealConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateRevealConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateRevealConfiguration)))
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 RevealConfiguration
-> Int -> UpdateRevealConfigurationResponse
UpdateRevealConfigurationResponse'
            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
"configuration")
            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 UpdateRevealConfiguration where
  hashWithSalt :: Int -> UpdateRevealConfiguration -> Int
hashWithSalt Int
_salt UpdateRevealConfiguration' {RevealConfiguration
configuration :: RevealConfiguration
$sel:configuration:UpdateRevealConfiguration' :: UpdateRevealConfiguration -> RevealConfiguration
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RevealConfiguration
configuration

instance Prelude.NFData UpdateRevealConfiguration where
  rnf :: UpdateRevealConfiguration -> ()
rnf UpdateRevealConfiguration' {RevealConfiguration
configuration :: RevealConfiguration
$sel:configuration:UpdateRevealConfiguration' :: UpdateRevealConfiguration -> RevealConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf RevealConfiguration
configuration

instance Data.ToHeaders UpdateRevealConfiguration where
  toHeaders :: UpdateRevealConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateRevealConfiguration where
  toJSON :: UpdateRevealConfiguration -> Value
toJSON UpdateRevealConfiguration' {RevealConfiguration
configuration :: RevealConfiguration
$sel:configuration:UpdateRevealConfiguration' :: UpdateRevealConfiguration -> RevealConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"configuration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RevealConfiguration
configuration)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateRevealConfigurationResponse' 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:
--
-- 'configuration', 'updateRevealConfigurationResponse_configuration' - The new configuration settings and the status of the configuration for
-- the account.
--
-- 'httpStatus', 'updateRevealConfigurationResponse_httpStatus' - The response's http status code.
newUpdateRevealConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRevealConfigurationResponse
newUpdateRevealConfigurationResponse :: Int -> UpdateRevealConfigurationResponse
newUpdateRevealConfigurationResponse Int
pHttpStatus_ =
  UpdateRevealConfigurationResponse'
    { $sel:configuration:UpdateRevealConfigurationResponse' :: Maybe RevealConfiguration
configuration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRevealConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The new configuration settings and the status of the configuration for
-- the account.
updateRevealConfigurationResponse_configuration :: Lens.Lens' UpdateRevealConfigurationResponse (Prelude.Maybe RevealConfiguration)
updateRevealConfigurationResponse_configuration :: Lens' UpdateRevealConfigurationResponse (Maybe RevealConfiguration)
updateRevealConfigurationResponse_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevealConfigurationResponse' {Maybe RevealConfiguration
configuration :: Maybe RevealConfiguration
$sel:configuration:UpdateRevealConfigurationResponse' :: UpdateRevealConfigurationResponse -> Maybe RevealConfiguration
configuration} -> Maybe RevealConfiguration
configuration) (\s :: UpdateRevealConfigurationResponse
s@UpdateRevealConfigurationResponse' {} Maybe RevealConfiguration
a -> UpdateRevealConfigurationResponse
s {$sel:configuration:UpdateRevealConfigurationResponse' :: Maybe RevealConfiguration
configuration = Maybe RevealConfiguration
a} :: UpdateRevealConfigurationResponse)

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

instance
  Prelude.NFData
    UpdateRevealConfigurationResponse
  where
  rnf :: UpdateRevealConfigurationResponse -> ()
rnf UpdateRevealConfigurationResponse' {Int
Maybe RevealConfiguration
httpStatus :: Int
configuration :: Maybe RevealConfiguration
$sel:httpStatus:UpdateRevealConfigurationResponse' :: UpdateRevealConfigurationResponse -> Int
$sel:configuration:UpdateRevealConfigurationResponse' :: UpdateRevealConfigurationResponse -> Maybe RevealConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe RevealConfiguration
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus