{-# 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.CreateDatalakeDelegatedAdmin
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Designates the Amazon Security Lake delegated administrator account for
-- the organization. This API can only be called by the organization
-- management account. The organization management account cannot be the
-- delegated administrator account.
module Amazonka.SecurityLake.CreateDatalakeDelegatedAdmin
  ( -- * Creating a Request
    CreateDatalakeDelegatedAdmin (..),
    newCreateDatalakeDelegatedAdmin,

    -- * Request Lenses
    createDatalakeDelegatedAdmin_account,

    -- * Destructuring the Response
    CreateDatalakeDelegatedAdminResponse (..),
    newCreateDatalakeDelegatedAdminResponse,

    -- * Response Lenses
    createDatalakeDelegatedAdminResponse_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:/ 'newCreateDatalakeDelegatedAdmin' smart constructor.
data CreateDatalakeDelegatedAdmin = CreateDatalakeDelegatedAdmin'
  { -- | The Amazon Web Services account ID of the Security Lake delegated
    -- administrator.
    CreateDatalakeDelegatedAdmin -> Text
account :: Prelude.Text
  }
  deriving (CreateDatalakeDelegatedAdmin
-> CreateDatalakeDelegatedAdmin -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDatalakeDelegatedAdmin
-> CreateDatalakeDelegatedAdmin -> Bool
$c/= :: CreateDatalakeDelegatedAdmin
-> CreateDatalakeDelegatedAdmin -> Bool
== :: CreateDatalakeDelegatedAdmin
-> CreateDatalakeDelegatedAdmin -> Bool
$c== :: CreateDatalakeDelegatedAdmin
-> CreateDatalakeDelegatedAdmin -> Bool
Prelude.Eq, ReadPrec [CreateDatalakeDelegatedAdmin]
ReadPrec CreateDatalakeDelegatedAdmin
Int -> ReadS CreateDatalakeDelegatedAdmin
ReadS [CreateDatalakeDelegatedAdmin]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDatalakeDelegatedAdmin]
$creadListPrec :: ReadPrec [CreateDatalakeDelegatedAdmin]
readPrec :: ReadPrec CreateDatalakeDelegatedAdmin
$creadPrec :: ReadPrec CreateDatalakeDelegatedAdmin
readList :: ReadS [CreateDatalakeDelegatedAdmin]
$creadList :: ReadS [CreateDatalakeDelegatedAdmin]
readsPrec :: Int -> ReadS CreateDatalakeDelegatedAdmin
$creadsPrec :: Int -> ReadS CreateDatalakeDelegatedAdmin
Prelude.Read, Int -> CreateDatalakeDelegatedAdmin -> ShowS
[CreateDatalakeDelegatedAdmin] -> ShowS
CreateDatalakeDelegatedAdmin -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDatalakeDelegatedAdmin] -> ShowS
$cshowList :: [CreateDatalakeDelegatedAdmin] -> ShowS
show :: CreateDatalakeDelegatedAdmin -> String
$cshow :: CreateDatalakeDelegatedAdmin -> String
showsPrec :: Int -> CreateDatalakeDelegatedAdmin -> ShowS
$cshowsPrec :: Int -> CreateDatalakeDelegatedAdmin -> ShowS
Prelude.Show, forall x.
Rep CreateDatalakeDelegatedAdmin x -> CreateDatalakeDelegatedAdmin
forall x.
CreateDatalakeDelegatedAdmin -> Rep CreateDatalakeDelegatedAdmin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDatalakeDelegatedAdmin x -> CreateDatalakeDelegatedAdmin
$cfrom :: forall x.
CreateDatalakeDelegatedAdmin -> Rep CreateDatalakeDelegatedAdmin x
Prelude.Generic)

-- |
-- Create a value of 'CreateDatalakeDelegatedAdmin' 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:
--
-- 'account', 'createDatalakeDelegatedAdmin_account' - The Amazon Web Services account ID of the Security Lake delegated
-- administrator.
newCreateDatalakeDelegatedAdmin ::
  -- | 'account'
  Prelude.Text ->
  CreateDatalakeDelegatedAdmin
newCreateDatalakeDelegatedAdmin :: Text -> CreateDatalakeDelegatedAdmin
newCreateDatalakeDelegatedAdmin Text
pAccount_ =
  CreateDatalakeDelegatedAdmin' {$sel:account:CreateDatalakeDelegatedAdmin' :: Text
account = Text
pAccount_}

-- | The Amazon Web Services account ID of the Security Lake delegated
-- administrator.
createDatalakeDelegatedAdmin_account :: Lens.Lens' CreateDatalakeDelegatedAdmin Prelude.Text
createDatalakeDelegatedAdmin_account :: Lens' CreateDatalakeDelegatedAdmin Text
createDatalakeDelegatedAdmin_account = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDatalakeDelegatedAdmin' {Text
account :: Text
$sel:account:CreateDatalakeDelegatedAdmin' :: CreateDatalakeDelegatedAdmin -> Text
account} -> Text
account) (\s :: CreateDatalakeDelegatedAdmin
s@CreateDatalakeDelegatedAdmin' {} Text
a -> CreateDatalakeDelegatedAdmin
s {$sel:account:CreateDatalakeDelegatedAdmin' :: Text
account = Text
a} :: CreateDatalakeDelegatedAdmin)

instance Core.AWSRequest CreateDatalakeDelegatedAdmin where
  type
    AWSResponse CreateDatalakeDelegatedAdmin =
      CreateDatalakeDelegatedAdminResponse
  request :: (Service -> Service)
-> CreateDatalakeDelegatedAdmin
-> Request CreateDatalakeDelegatedAdmin
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 CreateDatalakeDelegatedAdmin
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDatalakeDelegatedAdmin)))
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 -> CreateDatalakeDelegatedAdminResponse
CreateDatalakeDelegatedAdminResponse'
            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
    CreateDatalakeDelegatedAdmin
  where
  hashWithSalt :: Int -> CreateDatalakeDelegatedAdmin -> Int
hashWithSalt Int
_salt CreateDatalakeDelegatedAdmin' {Text
account :: Text
$sel:account:CreateDatalakeDelegatedAdmin' :: CreateDatalakeDelegatedAdmin -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
account

instance Prelude.NFData CreateDatalakeDelegatedAdmin where
  rnf :: CreateDatalakeDelegatedAdmin -> ()
rnf CreateDatalakeDelegatedAdmin' {Text
account :: Text
$sel:account:CreateDatalakeDelegatedAdmin' :: CreateDatalakeDelegatedAdmin -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
account

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

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

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

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

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

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

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