{-# 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.Inspector2.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 configurations for your Amazon Inspector organization.
module Amazonka.Inspector2.UpdateOrganizationConfiguration
  ( -- * Creating a Request
    UpdateOrganizationConfiguration (..),
    newUpdateOrganizationConfiguration,

    -- * Request Lenses
    updateOrganizationConfiguration_autoEnable,

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

    -- * Response Lenses
    updateOrganizationConfigurationResponse_httpStatus,
    updateOrganizationConfigurationResponse_autoEnable,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Inspector2.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'
  { -- | Defines which scan types are enabled automatically for new members of
    -- your Amazon Inspector organization.
    UpdateOrganizationConfiguration -> AutoEnable
autoEnable :: AutoEnable
  }
  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:
--
-- 'autoEnable', 'updateOrganizationConfiguration_autoEnable' - Defines which scan types are enabled automatically for new members of
-- your Amazon Inspector organization.
newUpdateOrganizationConfiguration ::
  -- | 'autoEnable'
  AutoEnable ->
  UpdateOrganizationConfiguration
newUpdateOrganizationConfiguration :: AutoEnable -> UpdateOrganizationConfiguration
newUpdateOrganizationConfiguration AutoEnable
pAutoEnable_ =
  UpdateOrganizationConfiguration'
    { $sel:autoEnable:UpdateOrganizationConfiguration' :: AutoEnable
autoEnable =
        AutoEnable
pAutoEnable_
    }

-- | Defines which scan types are enabled automatically for new members of
-- your Amazon Inspector organization.
updateOrganizationConfiguration_autoEnable :: Lens.Lens' UpdateOrganizationConfiguration AutoEnable
updateOrganizationConfiguration_autoEnable :: Lens' UpdateOrganizationConfiguration AutoEnable
updateOrganizationConfiguration_autoEnable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOrganizationConfiguration' {AutoEnable
autoEnable :: AutoEnable
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> AutoEnable
autoEnable} -> AutoEnable
autoEnable) (\s :: UpdateOrganizationConfiguration
s@UpdateOrganizationConfiguration' {} AutoEnable
a -> UpdateOrganizationConfiguration
s {$sel:autoEnable:UpdateOrganizationConfiguration' :: AutoEnable
autoEnable = AutoEnable
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 -> 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 ->
          Int -> AutoEnable -> 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"autoEnable")
      )

instance
  Prelude.Hashable
    UpdateOrganizationConfiguration
  where
  hashWithSalt :: Int -> UpdateOrganizationConfiguration -> Int
hashWithSalt
    Int
_salt
    UpdateOrganizationConfiguration' {AutoEnable
autoEnable :: AutoEnable
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> AutoEnable
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AutoEnable
autoEnable

instance
  Prelude.NFData
    UpdateOrganizationConfiguration
  where
  rnf :: UpdateOrganizationConfiguration -> ()
rnf UpdateOrganizationConfiguration' {AutoEnable
autoEnable :: AutoEnable
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> AutoEnable
..} =
    forall a. NFData a => a -> ()
Prelude.rnf AutoEnable
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' {AutoEnable
autoEnable :: AutoEnable
$sel:autoEnable:UpdateOrganizationConfiguration' :: UpdateOrganizationConfiguration -> AutoEnable
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"autoEnable" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AutoEnable
autoEnable)]
      )

instance Data.ToPath UpdateOrganizationConfiguration where
  toPath :: UpdateOrganizationConfiguration -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/organizationconfiguration/update"

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,
    -- | The updated status of scan types automatically enabled for new members
    -- of your Amazon Inspector organization.
    UpdateOrganizationConfigurationResponse -> AutoEnable
autoEnable :: AutoEnable
  }
  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.
--
-- 'autoEnable', 'updateOrganizationConfigurationResponse_autoEnable' - The updated status of scan types automatically enabled for new members
-- of your Amazon Inspector organization.
newUpdateOrganizationConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'autoEnable'
  AutoEnable ->
  UpdateOrganizationConfigurationResponse
newUpdateOrganizationConfigurationResponse :: Int -> AutoEnable -> UpdateOrganizationConfigurationResponse
newUpdateOrganizationConfigurationResponse
  Int
pHttpStatus_
  AutoEnable
pAutoEnable_ =
    UpdateOrganizationConfigurationResponse'
      { $sel:httpStatus:UpdateOrganizationConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:autoEnable:UpdateOrganizationConfigurationResponse' :: AutoEnable
autoEnable = AutoEnable
pAutoEnable_
      }

-- | 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)

-- | The updated status of scan types automatically enabled for new members
-- of your Amazon Inspector organization.
updateOrganizationConfigurationResponse_autoEnable :: Lens.Lens' UpdateOrganizationConfigurationResponse AutoEnable
updateOrganizationConfigurationResponse_autoEnable :: Lens' UpdateOrganizationConfigurationResponse AutoEnable
updateOrganizationConfigurationResponse_autoEnable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOrganizationConfigurationResponse' {AutoEnable
autoEnable :: AutoEnable
$sel:autoEnable:UpdateOrganizationConfigurationResponse' :: UpdateOrganizationConfigurationResponse -> AutoEnable
autoEnable} -> AutoEnable
autoEnable) (\s :: UpdateOrganizationConfigurationResponse
s@UpdateOrganizationConfigurationResponse' {} AutoEnable
a -> UpdateOrganizationConfigurationResponse
s {$sel:autoEnable:UpdateOrganizationConfigurationResponse' :: AutoEnable
autoEnable = AutoEnable
a} :: UpdateOrganizationConfigurationResponse)

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