{-# 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.GuardDuty.UpdateOrganizationConfiguration
-- 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 delegated administrator account with the values provided.
module Amazonka.GuardDuty.UpdateOrganizationConfiguration
  ( -- * Creating a Request
    UpdateOrganizationConfiguration (..),
    newUpdateOrganizationConfiguration,

    -- * Request Lenses
    updateOrganizationConfiguration_dataSources,
    updateOrganizationConfiguration_detectorId,
    updateOrganizationConfiguration_autoEnable,

    -- * Destructuring the Response
    UpdateOrganizationConfigurationResponse (..),
    newUpdateOrganizationConfigurationResponse,

    -- * Response Lenses
    updateOrganizationConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateOrganizationConfiguration' smart constructor.
data UpdateOrganizationConfiguration = UpdateOrganizationConfiguration'
  { -- | Describes which data sources will be updated.
    UpdateOrganizationConfiguration
-> Maybe OrganizationDataSourceConfigurations
dataSources :: Prelude.Maybe OrganizationDataSourceConfigurations,
    -- | The ID of the detector to update the delegated administrator for.
    UpdateOrganizationConfiguration -> Text
detectorId :: Prelude.Text,
    -- | Indicates whether to automatically enable member accounts in the
    -- organization.
    UpdateOrganizationConfiguration -> Bool
autoEnable :: Prelude.Bool
  }
  deriving (UpdateOrganizationConfiguration
-> UpdateOrganizationConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateOrganizationConfiguration
-> UpdateOrganizationConfiguration -> Bool
$c/= :: UpdateOrganizationConfiguration
-> UpdateOrganizationConfiguration -> Bool
== :: UpdateOrganizationConfiguration
-> UpdateOrganizationConfiguration -> Bool
$c== :: UpdateOrganizationConfiguration
-> UpdateOrganizationConfiguration -> Bool
Prelude.Eq, ReadPrec [UpdateOrganizationConfiguration]
ReadPrec UpdateOrganizationConfiguration
Int -> ReadS UpdateOrganizationConfiguration
ReadS [UpdateOrganizationConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateOrganizationConfiguration]
$creadListPrec :: ReadPrec [UpdateOrganizationConfiguration]
readPrec :: ReadPrec UpdateOrganizationConfiguration
$creadPrec :: ReadPrec UpdateOrganizationConfiguration
readList :: ReadS [UpdateOrganizationConfiguration]
$creadList :: ReadS [UpdateOrganizationConfiguration]
readsPrec :: Int -> ReadS UpdateOrganizationConfiguration
$creadsPrec :: Int -> ReadS UpdateOrganizationConfiguration
Prelude.Read, Int -> UpdateOrganizationConfiguration -> ShowS
[UpdateOrganizationConfiguration] -> ShowS
UpdateOrganizationConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateOrganizationConfiguration] -> ShowS
$cshowList :: [UpdateOrganizationConfiguration] -> ShowS
show :: UpdateOrganizationConfiguration -> String
$cshow :: UpdateOrganizationConfiguration -> String
showsPrec :: Int -> UpdateOrganizationConfiguration -> ShowS
$cshowsPrec :: Int -> UpdateOrganizationConfiguration -> ShowS
Prelude.Show, forall x.
Rep UpdateOrganizationConfiguration x
-> UpdateOrganizationConfiguration
forall x.
UpdateOrganizationConfiguration
-> Rep UpdateOrganizationConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateOrganizationConfiguration x
-> UpdateOrganizationConfiguration
$cfrom :: forall x.
UpdateOrganizationConfiguration
-> Rep UpdateOrganizationConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateOrganizationConfiguration' 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:
--
-- 'dataSources', 'updateOrganizationConfiguration_dataSources' - Describes which data sources will be updated.
--
-- 'detectorId', 'updateOrganizationConfiguration_detectorId' - The ID of the detector to update the delegated administrator for.
--
-- 'autoEnable', 'updateOrganizationConfiguration_autoEnable' - Indicates whether to automatically enable member accounts in the
-- organization.
newUpdateOrganizationConfiguration ::
  -- | 'detectorId'
  Prelude.Text ->
  -- | 'autoEnable'
  Prelude.Bool ->
  UpdateOrganizationConfiguration
newUpdateOrganizationConfiguration :: Text -> Bool -> UpdateOrganizationConfiguration
newUpdateOrganizationConfiguration
  Text
pDetectorId_
  Bool
pAutoEnable_ =
    UpdateOrganizationConfiguration'
      { $sel:dataSources:UpdateOrganizationConfiguration' :: Maybe OrganizationDataSourceConfigurations
dataSources =
          forall a. Maybe a
Prelude.Nothing,
        $sel:detectorId:UpdateOrganizationConfiguration' :: Text
detectorId = Text
pDetectorId_,
        $sel:autoEnable:UpdateOrganizationConfiguration' :: Bool
autoEnable = Bool
pAutoEnable_
      }

-- | Describes which data sources will be updated.
updateOrganizationConfiguration_dataSources :: Lens.Lens' UpdateOrganizationConfiguration (Prelude.Maybe OrganizationDataSourceConfigurations)
updateOrganizationConfiguration_dataSources :: Lens'
  UpdateOrganizationConfiguration
  (Maybe OrganizationDataSourceConfigurations)
updateOrganizationConfiguration_dataSources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOrganizationConfiguration' {Maybe OrganizationDataSourceConfigurations
dataSources :: Maybe OrganizationDataSourceConfigurations
$sel:dataSources:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration
-> Maybe OrganizationDataSourceConfigurations
dataSources} -> Maybe OrganizationDataSourceConfigurations
dataSources) (\s :: UpdateOrganizationConfiguration
s@UpdateOrganizationConfiguration' {} Maybe OrganizationDataSourceConfigurations
a -> UpdateOrganizationConfiguration
s {$sel:dataSources:UpdateOrganizationConfiguration' :: Maybe OrganizationDataSourceConfigurations
dataSources = Maybe OrganizationDataSourceConfigurations
a} :: UpdateOrganizationConfiguration)

-- | The ID of the detector to update the delegated administrator for.
updateOrganizationConfiguration_detectorId :: Lens.Lens' UpdateOrganizationConfiguration Prelude.Text
updateOrganizationConfiguration_detectorId :: Lens' UpdateOrganizationConfiguration Text
updateOrganizationConfiguration_detectorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOrganizationConfiguration' {Text
detectorId :: Text
$sel:detectorId:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Text
detectorId} -> Text
detectorId) (\s :: UpdateOrganizationConfiguration
s@UpdateOrganizationConfiguration' {} Text
a -> UpdateOrganizationConfiguration
s {$sel:detectorId:UpdateOrganizationConfiguration' :: Text
detectorId = Text
a} :: UpdateOrganizationConfiguration)

-- | Indicates whether to automatically enable member accounts in the
-- organization.
updateOrganizationConfiguration_autoEnable :: Lens.Lens' UpdateOrganizationConfiguration Prelude.Bool
updateOrganizationConfiguration_autoEnable :: Lens' UpdateOrganizationConfiguration Bool
updateOrganizationConfiguration_autoEnable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOrganizationConfiguration' {Bool
autoEnable :: Bool
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Bool
autoEnable} -> Bool
autoEnable) (\s :: UpdateOrganizationConfiguration
s@UpdateOrganizationConfiguration' {} Bool
a -> UpdateOrganizationConfiguration
s {$sel:autoEnable:UpdateOrganizationConfiguration' :: Bool
autoEnable = Bool
a} :: UpdateOrganizationConfiguration)

instance
  Core.AWSRequest
    UpdateOrganizationConfiguration
  where
  type
    AWSResponse UpdateOrganizationConfiguration =
      UpdateOrganizationConfigurationResponse
  request :: (Service -> Service)
-> UpdateOrganizationConfiguration
-> Request UpdateOrganizationConfiguration
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 UpdateOrganizationConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse UpdateOrganizationConfiguration)))
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 -> UpdateOrganizationConfigurationResponse
UpdateOrganizationConfigurationResponse'
            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
    UpdateOrganizationConfiguration
  where
  hashWithSalt :: Int -> UpdateOrganizationConfiguration -> Int
hashWithSalt
    Int
_salt
    UpdateOrganizationConfiguration' {Bool
Maybe OrganizationDataSourceConfigurations
Text
autoEnable :: Bool
detectorId :: Text
dataSources :: Maybe OrganizationDataSourceConfigurations
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Bool
$sel:detectorId:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Text
$sel:dataSources:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration
-> Maybe OrganizationDataSourceConfigurations
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OrganizationDataSourceConfigurations
dataSources
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
detectorId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
autoEnable

instance
  Prelude.NFData
    UpdateOrganizationConfiguration
  where
  rnf :: UpdateOrganizationConfiguration -> ()
rnf UpdateOrganizationConfiguration' {Bool
Maybe OrganizationDataSourceConfigurations
Text
autoEnable :: Bool
detectorId :: Text
dataSources :: Maybe OrganizationDataSourceConfigurations
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Bool
$sel:detectorId:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Text
$sel:dataSources:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration
-> Maybe OrganizationDataSourceConfigurations
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe OrganizationDataSourceConfigurations
dataSources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
detectorId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
autoEnable

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

instance Data.ToPath UpdateOrganizationConfiguration where
  toPath :: UpdateOrganizationConfiguration -> ByteString
toPath UpdateOrganizationConfiguration' {Bool
Maybe OrganizationDataSourceConfigurations
Text
autoEnable :: Bool
detectorId :: Text
dataSources :: Maybe OrganizationDataSourceConfigurations
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Bool
$sel:detectorId:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> Text
$sel:dataSources:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration
-> Maybe OrganizationDataSourceConfigurations
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/detector/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
detectorId, ByteString
"/admin"]

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

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

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

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

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