{-# 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.SecurityLake.CreateDatalakeAutoEnable
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Automatically enables Amazon Security Lake for new member accounts in
-- your organization. Security Lake is not automatically enabled for any
-- existing member accounts in your organization.
module Amazonka.SecurityLake.CreateDatalakeAutoEnable
  ( -- * Creating a Request
    CreateDatalakeAutoEnable (..),
    newCreateDatalakeAutoEnable,

    -- * Request Lenses
    createDatalakeAutoEnable_configurationForNewAccounts,

    -- * Destructuring the Response
    CreateDatalakeAutoEnableResponse (..),
    newCreateDatalakeAutoEnableResponse,

    -- * Response Lenses
    createDatalakeAutoEnableResponse_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.SecurityLake.Types

-- | /See:/ 'newCreateDatalakeAutoEnable' smart constructor.
data CreateDatalakeAutoEnable = CreateDatalakeAutoEnable'
  { -- | Enable Security Lake with the specified configuration settings to begin
    -- collecting security data for new accounts in your organization.
    CreateDatalakeAutoEnable -> [AutoEnableNewRegionConfiguration]
configurationForNewAccounts :: [AutoEnableNewRegionConfiguration]
  }
  deriving (CreateDatalakeAutoEnable -> CreateDatalakeAutoEnable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDatalakeAutoEnable -> CreateDatalakeAutoEnable -> Bool
$c/= :: CreateDatalakeAutoEnable -> CreateDatalakeAutoEnable -> Bool
== :: CreateDatalakeAutoEnable -> CreateDatalakeAutoEnable -> Bool
$c== :: CreateDatalakeAutoEnable -> CreateDatalakeAutoEnable -> Bool
Prelude.Eq, ReadPrec [CreateDatalakeAutoEnable]
ReadPrec CreateDatalakeAutoEnable
Int -> ReadS CreateDatalakeAutoEnable
ReadS [CreateDatalakeAutoEnable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDatalakeAutoEnable]
$creadListPrec :: ReadPrec [CreateDatalakeAutoEnable]
readPrec :: ReadPrec CreateDatalakeAutoEnable
$creadPrec :: ReadPrec CreateDatalakeAutoEnable
readList :: ReadS [CreateDatalakeAutoEnable]
$creadList :: ReadS [CreateDatalakeAutoEnable]
readsPrec :: Int -> ReadS CreateDatalakeAutoEnable
$creadsPrec :: Int -> ReadS CreateDatalakeAutoEnable
Prelude.Read, Int -> CreateDatalakeAutoEnable -> ShowS
[CreateDatalakeAutoEnable] -> ShowS
CreateDatalakeAutoEnable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDatalakeAutoEnable] -> ShowS
$cshowList :: [CreateDatalakeAutoEnable] -> ShowS
show :: CreateDatalakeAutoEnable -> String
$cshow :: CreateDatalakeAutoEnable -> String
showsPrec :: Int -> CreateDatalakeAutoEnable -> ShowS
$cshowsPrec :: Int -> CreateDatalakeAutoEnable -> ShowS
Prelude.Show, forall x.
Rep CreateDatalakeAutoEnable x -> CreateDatalakeAutoEnable
forall x.
CreateDatalakeAutoEnable -> Rep CreateDatalakeAutoEnable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDatalakeAutoEnable x -> CreateDatalakeAutoEnable
$cfrom :: forall x.
CreateDatalakeAutoEnable -> Rep CreateDatalakeAutoEnable x
Prelude.Generic)

-- |
-- Create a value of 'CreateDatalakeAutoEnable' 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:
--
-- 'configurationForNewAccounts', 'createDatalakeAutoEnable_configurationForNewAccounts' - Enable Security Lake with the specified configuration settings to begin
-- collecting security data for new accounts in your organization.
newCreateDatalakeAutoEnable ::
  CreateDatalakeAutoEnable
newCreateDatalakeAutoEnable :: CreateDatalakeAutoEnable
newCreateDatalakeAutoEnable =
  CreateDatalakeAutoEnable'
    { $sel:configurationForNewAccounts:CreateDatalakeAutoEnable' :: [AutoEnableNewRegionConfiguration]
configurationForNewAccounts =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | Enable Security Lake with the specified configuration settings to begin
-- collecting security data for new accounts in your organization.
createDatalakeAutoEnable_configurationForNewAccounts :: Lens.Lens' CreateDatalakeAutoEnable [AutoEnableNewRegionConfiguration]
createDatalakeAutoEnable_configurationForNewAccounts :: Lens' CreateDatalakeAutoEnable [AutoEnableNewRegionConfiguration]
createDatalakeAutoEnable_configurationForNewAccounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDatalakeAutoEnable' {[AutoEnableNewRegionConfiguration]
configurationForNewAccounts :: [AutoEnableNewRegionConfiguration]
$sel:configurationForNewAccounts:CreateDatalakeAutoEnable' :: CreateDatalakeAutoEnable -> [AutoEnableNewRegionConfiguration]
configurationForNewAccounts} -> [AutoEnableNewRegionConfiguration]
configurationForNewAccounts) (\s :: CreateDatalakeAutoEnable
s@CreateDatalakeAutoEnable' {} [AutoEnableNewRegionConfiguration]
a -> CreateDatalakeAutoEnable
s {$sel:configurationForNewAccounts:CreateDatalakeAutoEnable' :: [AutoEnableNewRegionConfiguration]
configurationForNewAccounts = [AutoEnableNewRegionConfiguration]
a} :: CreateDatalakeAutoEnable) 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 CreateDatalakeAutoEnable where
  type
    AWSResponse CreateDatalakeAutoEnable =
      CreateDatalakeAutoEnableResponse
  request :: (Service -> Service)
-> CreateDatalakeAutoEnable -> Request CreateDatalakeAutoEnable
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 CreateDatalakeAutoEnable
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDatalakeAutoEnable)))
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 -> CreateDatalakeAutoEnableResponse
CreateDatalakeAutoEnableResponse'
            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 CreateDatalakeAutoEnable where
  hashWithSalt :: Int -> CreateDatalakeAutoEnable -> Int
hashWithSalt Int
_salt CreateDatalakeAutoEnable' {[AutoEnableNewRegionConfiguration]
configurationForNewAccounts :: [AutoEnableNewRegionConfiguration]
$sel:configurationForNewAccounts:CreateDatalakeAutoEnable' :: CreateDatalakeAutoEnable -> [AutoEnableNewRegionConfiguration]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [AutoEnableNewRegionConfiguration]
configurationForNewAccounts

instance Prelude.NFData CreateDatalakeAutoEnable where
  rnf :: CreateDatalakeAutoEnable -> ()
rnf CreateDatalakeAutoEnable' {[AutoEnableNewRegionConfiguration]
configurationForNewAccounts :: [AutoEnableNewRegionConfiguration]
$sel:configurationForNewAccounts:CreateDatalakeAutoEnable' :: CreateDatalakeAutoEnable -> [AutoEnableNewRegionConfiguration]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [AutoEnableNewRegionConfiguration]
configurationForNewAccounts

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

instance Data.ToPath CreateDatalakeAutoEnable where
  toPath :: CreateDatalakeAutoEnable -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/datalake/autoenable"

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

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

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

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

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