{-# 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.UpdateAutomatedDiscoveryConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables or disables automated sensitive data discovery for an account.
module Amazonka.MacieV2.UpdateAutomatedDiscoveryConfiguration
  ( -- * Creating a Request
    UpdateAutomatedDiscoveryConfiguration (..),
    newUpdateAutomatedDiscoveryConfiguration,

    -- * Request Lenses
    updateAutomatedDiscoveryConfiguration_status,

    -- * Destructuring the Response
    UpdateAutomatedDiscoveryConfigurationResponse (..),
    newUpdateAutomatedDiscoveryConfigurationResponse,

    -- * Response Lenses
    updateAutomatedDiscoveryConfigurationResponse_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:/ 'newUpdateAutomatedDiscoveryConfiguration' smart constructor.
data UpdateAutomatedDiscoveryConfiguration = UpdateAutomatedDiscoveryConfiguration'
  { -- | The new status of automated sensitive data discovery for the account.
    -- Valid values are: ENABLED, start or resume automated sensitive data
    -- discovery activities for the account; and, DISABLED, stop performing
    -- automated sensitive data discovery activities for the account.
    --
    -- When you enable automated sensitive data discovery for the first time,
    -- Amazon Macie uses default configuration settings to determine which data
    -- sources to analyze and which managed data identifiers to use. To change
    -- these settings, use the UpdateClassificationScope and
    -- UpdateSensitivityInspectionTemplate operations, respectively. If you
    -- change the settings and subsequently disable the configuration, Amazon
    -- Macie retains your changes.
    UpdateAutomatedDiscoveryConfiguration -> AutomatedDiscoveryStatus
status :: AutomatedDiscoveryStatus
  }
  deriving (UpdateAutomatedDiscoveryConfiguration
-> UpdateAutomatedDiscoveryConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAutomatedDiscoveryConfiguration
-> UpdateAutomatedDiscoveryConfiguration -> Bool
$c/= :: UpdateAutomatedDiscoveryConfiguration
-> UpdateAutomatedDiscoveryConfiguration -> Bool
== :: UpdateAutomatedDiscoveryConfiguration
-> UpdateAutomatedDiscoveryConfiguration -> Bool
$c== :: UpdateAutomatedDiscoveryConfiguration
-> UpdateAutomatedDiscoveryConfiguration -> Bool
Prelude.Eq, ReadPrec [UpdateAutomatedDiscoveryConfiguration]
ReadPrec UpdateAutomatedDiscoveryConfiguration
Int -> ReadS UpdateAutomatedDiscoveryConfiguration
ReadS [UpdateAutomatedDiscoveryConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateAutomatedDiscoveryConfiguration]
$creadListPrec :: ReadPrec [UpdateAutomatedDiscoveryConfiguration]
readPrec :: ReadPrec UpdateAutomatedDiscoveryConfiguration
$creadPrec :: ReadPrec UpdateAutomatedDiscoveryConfiguration
readList :: ReadS [UpdateAutomatedDiscoveryConfiguration]
$creadList :: ReadS [UpdateAutomatedDiscoveryConfiguration]
readsPrec :: Int -> ReadS UpdateAutomatedDiscoveryConfiguration
$creadsPrec :: Int -> ReadS UpdateAutomatedDiscoveryConfiguration
Prelude.Read, Int -> UpdateAutomatedDiscoveryConfiguration -> ShowS
[UpdateAutomatedDiscoveryConfiguration] -> ShowS
UpdateAutomatedDiscoveryConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAutomatedDiscoveryConfiguration] -> ShowS
$cshowList :: [UpdateAutomatedDiscoveryConfiguration] -> ShowS
show :: UpdateAutomatedDiscoveryConfiguration -> String
$cshow :: UpdateAutomatedDiscoveryConfiguration -> String
showsPrec :: Int -> UpdateAutomatedDiscoveryConfiguration -> ShowS
$cshowsPrec :: Int -> UpdateAutomatedDiscoveryConfiguration -> ShowS
Prelude.Show, forall x.
Rep UpdateAutomatedDiscoveryConfiguration x
-> UpdateAutomatedDiscoveryConfiguration
forall x.
UpdateAutomatedDiscoveryConfiguration
-> Rep UpdateAutomatedDiscoveryConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateAutomatedDiscoveryConfiguration x
-> UpdateAutomatedDiscoveryConfiguration
$cfrom :: forall x.
UpdateAutomatedDiscoveryConfiguration
-> Rep UpdateAutomatedDiscoveryConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateAutomatedDiscoveryConfiguration' 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:
--
-- 'status', 'updateAutomatedDiscoveryConfiguration_status' - The new status of automated sensitive data discovery for the account.
-- Valid values are: ENABLED, start or resume automated sensitive data
-- discovery activities for the account; and, DISABLED, stop performing
-- automated sensitive data discovery activities for the account.
--
-- When you enable automated sensitive data discovery for the first time,
-- Amazon Macie uses default configuration settings to determine which data
-- sources to analyze and which managed data identifiers to use. To change
-- these settings, use the UpdateClassificationScope and
-- UpdateSensitivityInspectionTemplate operations, respectively. If you
-- change the settings and subsequently disable the configuration, Amazon
-- Macie retains your changes.
newUpdateAutomatedDiscoveryConfiguration ::
  -- | 'status'
  AutomatedDiscoveryStatus ->
  UpdateAutomatedDiscoveryConfiguration
newUpdateAutomatedDiscoveryConfiguration :: AutomatedDiscoveryStatus -> UpdateAutomatedDiscoveryConfiguration
newUpdateAutomatedDiscoveryConfiguration AutomatedDiscoveryStatus
pStatus_ =
  UpdateAutomatedDiscoveryConfiguration'
    { $sel:status:UpdateAutomatedDiscoveryConfiguration' :: AutomatedDiscoveryStatus
status =
        AutomatedDiscoveryStatus
pStatus_
    }

-- | The new status of automated sensitive data discovery for the account.
-- Valid values are: ENABLED, start or resume automated sensitive data
-- discovery activities for the account; and, DISABLED, stop performing
-- automated sensitive data discovery activities for the account.
--
-- When you enable automated sensitive data discovery for the first time,
-- Amazon Macie uses default configuration settings to determine which data
-- sources to analyze and which managed data identifiers to use. To change
-- these settings, use the UpdateClassificationScope and
-- UpdateSensitivityInspectionTemplate operations, respectively. If you
-- change the settings and subsequently disable the configuration, Amazon
-- Macie retains your changes.
updateAutomatedDiscoveryConfiguration_status :: Lens.Lens' UpdateAutomatedDiscoveryConfiguration AutomatedDiscoveryStatus
updateAutomatedDiscoveryConfiguration_status :: Lens'
  UpdateAutomatedDiscoveryConfiguration AutomatedDiscoveryStatus
updateAutomatedDiscoveryConfiguration_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutomatedDiscoveryConfiguration' {AutomatedDiscoveryStatus
status :: AutomatedDiscoveryStatus
$sel:status:UpdateAutomatedDiscoveryConfiguration' :: UpdateAutomatedDiscoveryConfiguration -> AutomatedDiscoveryStatus
status} -> AutomatedDiscoveryStatus
status) (\s :: UpdateAutomatedDiscoveryConfiguration
s@UpdateAutomatedDiscoveryConfiguration' {} AutomatedDiscoveryStatus
a -> UpdateAutomatedDiscoveryConfiguration
s {$sel:status:UpdateAutomatedDiscoveryConfiguration' :: AutomatedDiscoveryStatus
status = AutomatedDiscoveryStatus
a} :: UpdateAutomatedDiscoveryConfiguration)

instance
  Core.AWSRequest
    UpdateAutomatedDiscoveryConfiguration
  where
  type
    AWSResponse
      UpdateAutomatedDiscoveryConfiguration =
      UpdateAutomatedDiscoveryConfigurationResponse
  request :: (Service -> Service)
-> UpdateAutomatedDiscoveryConfiguration
-> Request UpdateAutomatedDiscoveryConfiguration
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 UpdateAutomatedDiscoveryConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse UpdateAutomatedDiscoveryConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateAutomatedDiscoveryConfigurationResponse
UpdateAutomatedDiscoveryConfigurationResponse'
            forall (f :: * -> *) a b. Functor 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
    UpdateAutomatedDiscoveryConfiguration
  where
  hashWithSalt :: Int -> UpdateAutomatedDiscoveryConfiguration -> Int
hashWithSalt
    Int
_salt
    UpdateAutomatedDiscoveryConfiguration' {AutomatedDiscoveryStatus
status :: AutomatedDiscoveryStatus
$sel:status:UpdateAutomatedDiscoveryConfiguration' :: UpdateAutomatedDiscoveryConfiguration -> AutomatedDiscoveryStatus
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AutomatedDiscoveryStatus
status

instance
  Prelude.NFData
    UpdateAutomatedDiscoveryConfiguration
  where
  rnf :: UpdateAutomatedDiscoveryConfiguration -> ()
rnf UpdateAutomatedDiscoveryConfiguration' {AutomatedDiscoveryStatus
status :: AutomatedDiscoveryStatus
$sel:status:UpdateAutomatedDiscoveryConfiguration' :: UpdateAutomatedDiscoveryConfiguration -> AutomatedDiscoveryStatus
..} =
    forall a. NFData a => a -> ()
Prelude.rnf AutomatedDiscoveryStatus
status

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

instance
  Data.ToPath
    UpdateAutomatedDiscoveryConfiguration
  where
  toPath :: UpdateAutomatedDiscoveryConfiguration -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/automated-discovery/configuration"

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

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

-- |
-- Create a value of 'UpdateAutomatedDiscoveryConfigurationResponse' 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:
--
-- 'httpStatus', 'updateAutomatedDiscoveryConfigurationResponse_httpStatus' - The response's http status code.
newUpdateAutomatedDiscoveryConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateAutomatedDiscoveryConfigurationResponse
newUpdateAutomatedDiscoveryConfigurationResponse :: Int -> UpdateAutomatedDiscoveryConfigurationResponse
newUpdateAutomatedDiscoveryConfigurationResponse
  Int
pHttpStatus_ =
    UpdateAutomatedDiscoveryConfigurationResponse'
      { $sel:httpStatus:UpdateAutomatedDiscoveryConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

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

instance
  Prelude.NFData
    UpdateAutomatedDiscoveryConfigurationResponse
  where
  rnf :: UpdateAutomatedDiscoveryConfigurationResponse -> ()
rnf
    UpdateAutomatedDiscoveryConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateAutomatedDiscoveryConfigurationResponse' :: UpdateAutomatedDiscoveryConfigurationResponse -> Int
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus