{-# 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.Enable
-- 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 Amazon Inspector scans for one or more Amazon Web Services
-- accounts.
module Amazonka.Inspector2.Enable
  ( -- * Creating a Request
    Enable (..),
    newEnable,

    -- * Request Lenses
    enable_accountIds,
    enable_clientToken,
    enable_resourceTypes,

    -- * Destructuring the Response
    EnableResponse (..),
    newEnableResponse,

    -- * Response Lenses
    enableResponse_failedAccounts,
    enableResponse_httpStatus,
    enableResponse_accounts,
  )
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:/ 'newEnable' smart constructor.
data Enable = Enable'
  { -- | A list of account IDs you want to enable Amazon Inspector scans for.
    Enable -> Maybe [Text]
accountIds :: Prelude.Maybe [Prelude.Text],
    -- | The idempotency token for the request.
    Enable -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The resource scan types you want to enable.
    Enable -> NonEmpty ResourceScanType
resourceTypes :: Prelude.NonEmpty ResourceScanType
  }
  deriving (Enable -> Enable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Enable -> Enable -> Bool
$c/= :: Enable -> Enable -> Bool
== :: Enable -> Enable -> Bool
$c== :: Enable -> Enable -> Bool
Prelude.Eq, ReadPrec [Enable]
ReadPrec Enable
Int -> ReadS Enable
ReadS [Enable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Enable]
$creadListPrec :: ReadPrec [Enable]
readPrec :: ReadPrec Enable
$creadPrec :: ReadPrec Enable
readList :: ReadS [Enable]
$creadList :: ReadS [Enable]
readsPrec :: Int -> ReadS Enable
$creadsPrec :: Int -> ReadS Enable
Prelude.Read, Int -> Enable -> ShowS
[Enable] -> ShowS
Enable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Enable] -> ShowS
$cshowList :: [Enable] -> ShowS
show :: Enable -> String
$cshow :: Enable -> String
showsPrec :: Int -> Enable -> ShowS
$cshowsPrec :: Int -> Enable -> ShowS
Prelude.Show, forall x. Rep Enable x -> Enable
forall x. Enable -> Rep Enable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Enable x -> Enable
$cfrom :: forall x. Enable -> Rep Enable x
Prelude.Generic)

-- |
-- Create a value of 'Enable' 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:
--
-- 'accountIds', 'enable_accountIds' - A list of account IDs you want to enable Amazon Inspector scans for.
--
-- 'clientToken', 'enable_clientToken' - The idempotency token for the request.
--
-- 'resourceTypes', 'enable_resourceTypes' - The resource scan types you want to enable.
newEnable ::
  -- | 'resourceTypes'
  Prelude.NonEmpty ResourceScanType ->
  Enable
newEnable :: NonEmpty ResourceScanType -> Enable
newEnable NonEmpty ResourceScanType
pResourceTypes_ =
  Enable'
    { $sel:accountIds:Enable' :: Maybe [Text]
accountIds = forall a. Maybe a
Prelude.Nothing,
      $sel:clientToken:Enable' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceTypes:Enable' :: NonEmpty ResourceScanType
resourceTypes = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty ResourceScanType
pResourceTypes_
    }

-- | A list of account IDs you want to enable Amazon Inspector scans for.
enable_accountIds :: Lens.Lens' Enable (Prelude.Maybe [Prelude.Text])
enable_accountIds :: Lens' Enable (Maybe [Text])
enable_accountIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Enable' {Maybe [Text]
accountIds :: Maybe [Text]
$sel:accountIds:Enable' :: Enable -> Maybe [Text]
accountIds} -> Maybe [Text]
accountIds) (\s :: Enable
s@Enable' {} Maybe [Text]
a -> Enable
s {$sel:accountIds:Enable' :: Maybe [Text]
accountIds = Maybe [Text]
a} :: Enable) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The idempotency token for the request.
enable_clientToken :: Lens.Lens' Enable (Prelude.Maybe Prelude.Text)
enable_clientToken :: Lens' Enable (Maybe Text)
enable_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Enable' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:Enable' :: Enable -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: Enable
s@Enable' {} Maybe Text
a -> Enable
s {$sel:clientToken:Enable' :: Maybe Text
clientToken = Maybe Text
a} :: Enable)

-- | The resource scan types you want to enable.
enable_resourceTypes :: Lens.Lens' Enable (Prelude.NonEmpty ResourceScanType)
enable_resourceTypes :: Lens' Enable (NonEmpty ResourceScanType)
enable_resourceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Enable' {NonEmpty ResourceScanType
resourceTypes :: NonEmpty ResourceScanType
$sel:resourceTypes:Enable' :: Enable -> NonEmpty ResourceScanType
resourceTypes} -> NonEmpty ResourceScanType
resourceTypes) (\s :: Enable
s@Enable' {} NonEmpty ResourceScanType
a -> Enable
s {$sel:resourceTypes:Enable' :: NonEmpty ResourceScanType
resourceTypes = NonEmpty ResourceScanType
a} :: Enable) 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 Enable where
  type AWSResponse Enable = EnableResponse
  request :: (Service -> Service) -> Enable -> Request Enable
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 Enable
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse Enable)))
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 ->
          Maybe [FailedAccount] -> Int -> [Account] -> EnableResponse
EnableResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"failedAccounts" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => 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 (Maybe a)
Data..?> Key
"accounts" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable Enable where
  hashWithSalt :: Int -> Enable -> Int
hashWithSalt Int
_salt Enable' {Maybe [Text]
Maybe Text
NonEmpty ResourceScanType
resourceTypes :: NonEmpty ResourceScanType
clientToken :: Maybe Text
accountIds :: Maybe [Text]
$sel:resourceTypes:Enable' :: Enable -> NonEmpty ResourceScanType
$sel:clientToken:Enable' :: Enable -> Maybe Text
$sel:accountIds:Enable' :: Enable -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
accountIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty ResourceScanType
resourceTypes

instance Prelude.NFData Enable where
  rnf :: Enable -> ()
rnf Enable' {Maybe [Text]
Maybe Text
NonEmpty ResourceScanType
resourceTypes :: NonEmpty ResourceScanType
clientToken :: Maybe Text
accountIds :: Maybe [Text]
$sel:resourceTypes:Enable' :: Enable -> NonEmpty ResourceScanType
$sel:clientToken:Enable' :: Enable -> Maybe Text
$sel:accountIds:Enable' :: Enable -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
accountIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty ResourceScanType
resourceTypes

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

instance Data.ToPath Enable where
  toPath :: Enable -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/enable"

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

-- | /See:/ 'newEnableResponse' smart constructor.
data EnableResponse = EnableResponse'
  { -- | Information on any accounts for which Amazon Inspector scans could not
    -- be enabled. Details are provided for each account.
    EnableResponse -> Maybe [FailedAccount]
failedAccounts :: Prelude.Maybe [FailedAccount],
    -- | The response's http status code.
    EnableResponse -> Int
httpStatus :: Prelude.Int,
    -- | Information on the accounts that have had Amazon Inspector scans
    -- successfully enabled. Details are provided for each account.
    EnableResponse -> [Account]
accounts :: [Account]
  }
  deriving (EnableResponse -> EnableResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableResponse -> EnableResponse -> Bool
$c/= :: EnableResponse -> EnableResponse -> Bool
== :: EnableResponse -> EnableResponse -> Bool
$c== :: EnableResponse -> EnableResponse -> Bool
Prelude.Eq, ReadPrec [EnableResponse]
ReadPrec EnableResponse
Int -> ReadS EnableResponse
ReadS [EnableResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableResponse]
$creadListPrec :: ReadPrec [EnableResponse]
readPrec :: ReadPrec EnableResponse
$creadPrec :: ReadPrec EnableResponse
readList :: ReadS [EnableResponse]
$creadList :: ReadS [EnableResponse]
readsPrec :: Int -> ReadS EnableResponse
$creadsPrec :: Int -> ReadS EnableResponse
Prelude.Read, Int -> EnableResponse -> ShowS
[EnableResponse] -> ShowS
EnableResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableResponse] -> ShowS
$cshowList :: [EnableResponse] -> ShowS
show :: EnableResponse -> String
$cshow :: EnableResponse -> String
showsPrec :: Int -> EnableResponse -> ShowS
$cshowsPrec :: Int -> EnableResponse -> ShowS
Prelude.Show, forall x. Rep EnableResponse x -> EnableResponse
forall x. EnableResponse -> Rep EnableResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableResponse x -> EnableResponse
$cfrom :: forall x. EnableResponse -> Rep EnableResponse x
Prelude.Generic)

-- |
-- Create a value of 'EnableResponse' 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:
--
-- 'failedAccounts', 'enableResponse_failedAccounts' - Information on any accounts for which Amazon Inspector scans could not
-- be enabled. Details are provided for each account.
--
-- 'httpStatus', 'enableResponse_httpStatus' - The response's http status code.
--
-- 'accounts', 'enableResponse_accounts' - Information on the accounts that have had Amazon Inspector scans
-- successfully enabled. Details are provided for each account.
newEnableResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  EnableResponse
newEnableResponse :: Int -> EnableResponse
newEnableResponse Int
pHttpStatus_ =
  EnableResponse'
    { $sel:failedAccounts:EnableResponse' :: Maybe [FailedAccount]
failedAccounts = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:EnableResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:accounts:EnableResponse' :: [Account]
accounts = forall a. Monoid a => a
Prelude.mempty
    }

-- | Information on any accounts for which Amazon Inspector scans could not
-- be enabled. Details are provided for each account.
enableResponse_failedAccounts :: Lens.Lens' EnableResponse (Prelude.Maybe [FailedAccount])
enableResponse_failedAccounts :: Lens' EnableResponse (Maybe [FailedAccount])
enableResponse_failedAccounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableResponse' {Maybe [FailedAccount]
failedAccounts :: Maybe [FailedAccount]
$sel:failedAccounts:EnableResponse' :: EnableResponse -> Maybe [FailedAccount]
failedAccounts} -> Maybe [FailedAccount]
failedAccounts) (\s :: EnableResponse
s@EnableResponse' {} Maybe [FailedAccount]
a -> EnableResponse
s {$sel:failedAccounts:EnableResponse' :: Maybe [FailedAccount]
failedAccounts = Maybe [FailedAccount]
a} :: EnableResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

-- | Information on the accounts that have had Amazon Inspector scans
-- successfully enabled. Details are provided for each account.
enableResponse_accounts :: Lens.Lens' EnableResponse [Account]
enableResponse_accounts :: Lens' EnableResponse [Account]
enableResponse_accounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableResponse' {[Account]
accounts :: [Account]
$sel:accounts:EnableResponse' :: EnableResponse -> [Account]
accounts} -> [Account]
accounts) (\s :: EnableResponse
s@EnableResponse' {} [Account]
a -> EnableResponse
s {$sel:accounts:EnableResponse' :: [Account]
accounts = [Account]
a} :: EnableResponse) 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 Prelude.NFData EnableResponse where
  rnf :: EnableResponse -> ()
rnf EnableResponse' {Int
[Account]
Maybe [FailedAccount]
accounts :: [Account]
httpStatus :: Int
failedAccounts :: Maybe [FailedAccount]
$sel:accounts:EnableResponse' :: EnableResponse -> [Account]
$sel:httpStatus:EnableResponse' :: EnableResponse -> Int
$sel:failedAccounts:EnableResponse' :: EnableResponse -> Maybe [FailedAccount]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [FailedAccount]
failedAccounts
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [Account]
accounts