{-# 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.CloudTrail.PutInsightSelectors
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lets you enable Insights event logging by specifying the Insights
-- selectors that you want to enable on an existing trail. You also use
-- @PutInsightSelectors@ to turn off Insights event logging, by passing an
-- empty list of insight types. The valid Insights event types in this
-- release are @ApiErrorRateInsight@ and @ApiCallRateInsight@.
module Amazonka.CloudTrail.PutInsightSelectors
  ( -- * Creating a Request
    PutInsightSelectors (..),
    newPutInsightSelectors,

    -- * Request Lenses
    putInsightSelectors_trailName,
    putInsightSelectors_insightSelectors,

    -- * Destructuring the Response
    PutInsightSelectorsResponse (..),
    newPutInsightSelectorsResponse,

    -- * Response Lenses
    putInsightSelectorsResponse_insightSelectors,
    putInsightSelectorsResponse_trailARN,
    putInsightSelectorsResponse_httpStatus,
  )
where

import Amazonka.CloudTrail.Types
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

-- | /See:/ 'newPutInsightSelectors' smart constructor.
data PutInsightSelectors = PutInsightSelectors'
  { -- | The name of the CloudTrail trail for which you want to change or add
    -- Insights selectors.
    PutInsightSelectors -> Text
trailName :: Prelude.Text,
    -- | A JSON string that contains the insight types you want to log on a
    -- trail. @ApiCallRateInsight@ and @ApiErrorRateInsight@ are valid insight
    -- types.
    PutInsightSelectors -> [InsightSelector]
insightSelectors :: [InsightSelector]
  }
  deriving (PutInsightSelectors -> PutInsightSelectors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutInsightSelectors -> PutInsightSelectors -> Bool
$c/= :: PutInsightSelectors -> PutInsightSelectors -> Bool
== :: PutInsightSelectors -> PutInsightSelectors -> Bool
$c== :: PutInsightSelectors -> PutInsightSelectors -> Bool
Prelude.Eq, ReadPrec [PutInsightSelectors]
ReadPrec PutInsightSelectors
Int -> ReadS PutInsightSelectors
ReadS [PutInsightSelectors]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutInsightSelectors]
$creadListPrec :: ReadPrec [PutInsightSelectors]
readPrec :: ReadPrec PutInsightSelectors
$creadPrec :: ReadPrec PutInsightSelectors
readList :: ReadS [PutInsightSelectors]
$creadList :: ReadS [PutInsightSelectors]
readsPrec :: Int -> ReadS PutInsightSelectors
$creadsPrec :: Int -> ReadS PutInsightSelectors
Prelude.Read, Int -> PutInsightSelectors -> ShowS
[PutInsightSelectors] -> ShowS
PutInsightSelectors -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutInsightSelectors] -> ShowS
$cshowList :: [PutInsightSelectors] -> ShowS
show :: PutInsightSelectors -> String
$cshow :: PutInsightSelectors -> String
showsPrec :: Int -> PutInsightSelectors -> ShowS
$cshowsPrec :: Int -> PutInsightSelectors -> ShowS
Prelude.Show, forall x. Rep PutInsightSelectors x -> PutInsightSelectors
forall x. PutInsightSelectors -> Rep PutInsightSelectors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutInsightSelectors x -> PutInsightSelectors
$cfrom :: forall x. PutInsightSelectors -> Rep PutInsightSelectors x
Prelude.Generic)

-- |
-- Create a value of 'PutInsightSelectors' 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:
--
-- 'trailName', 'putInsightSelectors_trailName' - The name of the CloudTrail trail for which you want to change or add
-- Insights selectors.
--
-- 'insightSelectors', 'putInsightSelectors_insightSelectors' - A JSON string that contains the insight types you want to log on a
-- trail. @ApiCallRateInsight@ and @ApiErrorRateInsight@ are valid insight
-- types.
newPutInsightSelectors ::
  -- | 'trailName'
  Prelude.Text ->
  PutInsightSelectors
newPutInsightSelectors :: Text -> PutInsightSelectors
newPutInsightSelectors Text
pTrailName_ =
  PutInsightSelectors'
    { $sel:trailName:PutInsightSelectors' :: Text
trailName = Text
pTrailName_,
      $sel:insightSelectors:PutInsightSelectors' :: [InsightSelector]
insightSelectors = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the CloudTrail trail for which you want to change or add
-- Insights selectors.
putInsightSelectors_trailName :: Lens.Lens' PutInsightSelectors Prelude.Text
putInsightSelectors_trailName :: Lens' PutInsightSelectors Text
putInsightSelectors_trailName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightSelectors' {Text
trailName :: Text
$sel:trailName:PutInsightSelectors' :: PutInsightSelectors -> Text
trailName} -> Text
trailName) (\s :: PutInsightSelectors
s@PutInsightSelectors' {} Text
a -> PutInsightSelectors
s {$sel:trailName:PutInsightSelectors' :: Text
trailName = Text
a} :: PutInsightSelectors)

-- | A JSON string that contains the insight types you want to log on a
-- trail. @ApiCallRateInsight@ and @ApiErrorRateInsight@ are valid insight
-- types.
putInsightSelectors_insightSelectors :: Lens.Lens' PutInsightSelectors [InsightSelector]
putInsightSelectors_insightSelectors :: Lens' PutInsightSelectors [InsightSelector]
putInsightSelectors_insightSelectors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightSelectors' {[InsightSelector]
insightSelectors :: [InsightSelector]
$sel:insightSelectors:PutInsightSelectors' :: PutInsightSelectors -> [InsightSelector]
insightSelectors} -> [InsightSelector]
insightSelectors) (\s :: PutInsightSelectors
s@PutInsightSelectors' {} [InsightSelector]
a -> PutInsightSelectors
s {$sel:insightSelectors:PutInsightSelectors' :: [InsightSelector]
insightSelectors = [InsightSelector]
a} :: PutInsightSelectors) 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 PutInsightSelectors where
  type
    AWSResponse PutInsightSelectors =
      PutInsightSelectorsResponse
  request :: (Service -> Service)
-> PutInsightSelectors -> Request PutInsightSelectors
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 PutInsightSelectors
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutInsightSelectors)))
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 [InsightSelector]
-> Maybe Text -> Int -> PutInsightSelectorsResponse
PutInsightSelectorsResponse'
            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
"InsightSelectors"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"TrailARN")
            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))
      )

instance Prelude.Hashable PutInsightSelectors where
  hashWithSalt :: Int -> PutInsightSelectors -> Int
hashWithSalt Int
_salt PutInsightSelectors' {[InsightSelector]
Text
insightSelectors :: [InsightSelector]
trailName :: Text
$sel:insightSelectors:PutInsightSelectors' :: PutInsightSelectors -> [InsightSelector]
$sel:trailName:PutInsightSelectors' :: PutInsightSelectors -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
trailName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [InsightSelector]
insightSelectors

instance Prelude.NFData PutInsightSelectors where
  rnf :: PutInsightSelectors -> ()
rnf PutInsightSelectors' {[InsightSelector]
Text
insightSelectors :: [InsightSelector]
trailName :: Text
$sel:insightSelectors:PutInsightSelectors' :: PutInsightSelectors -> [InsightSelector]
$sel:trailName:PutInsightSelectors' :: PutInsightSelectors -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
trailName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [InsightSelector]
insightSelectors

instance Data.ToHeaders PutInsightSelectors where
  toHeaders :: PutInsightSelectors -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"com.amazonaws.cloudtrail.v20131101.CloudTrail_20131101.PutInsightSelectors" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON PutInsightSelectors where
  toJSON :: PutInsightSelectors -> Value
toJSON PutInsightSelectors' {[InsightSelector]
Text
insightSelectors :: [InsightSelector]
trailName :: Text
$sel:insightSelectors:PutInsightSelectors' :: PutInsightSelectors -> [InsightSelector]
$sel:trailName:PutInsightSelectors' :: PutInsightSelectors -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"TrailName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
trailName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"InsightSelectors" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [InsightSelector]
insightSelectors)
          ]
      )

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

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

-- | /See:/ 'newPutInsightSelectorsResponse' smart constructor.
data PutInsightSelectorsResponse = PutInsightSelectorsResponse'
  { -- | A JSON string that contains the Insights event types that you want to
    -- log on a trail. The valid Insights types in this release are
    -- @ApiErrorRateInsight@ and @ApiCallRateInsight@.
    PutInsightSelectorsResponse -> Maybe [InsightSelector]
insightSelectors :: Prelude.Maybe [InsightSelector],
    -- | The Amazon Resource Name (ARN) of a trail for which you want to change
    -- or add Insights selectors.
    PutInsightSelectorsResponse -> Maybe Text
trailARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    PutInsightSelectorsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PutInsightSelectorsResponse -> PutInsightSelectorsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutInsightSelectorsResponse -> PutInsightSelectorsResponse -> Bool
$c/= :: PutInsightSelectorsResponse -> PutInsightSelectorsResponse -> Bool
== :: PutInsightSelectorsResponse -> PutInsightSelectorsResponse -> Bool
$c== :: PutInsightSelectorsResponse -> PutInsightSelectorsResponse -> Bool
Prelude.Eq, ReadPrec [PutInsightSelectorsResponse]
ReadPrec PutInsightSelectorsResponse
Int -> ReadS PutInsightSelectorsResponse
ReadS [PutInsightSelectorsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutInsightSelectorsResponse]
$creadListPrec :: ReadPrec [PutInsightSelectorsResponse]
readPrec :: ReadPrec PutInsightSelectorsResponse
$creadPrec :: ReadPrec PutInsightSelectorsResponse
readList :: ReadS [PutInsightSelectorsResponse]
$creadList :: ReadS [PutInsightSelectorsResponse]
readsPrec :: Int -> ReadS PutInsightSelectorsResponse
$creadsPrec :: Int -> ReadS PutInsightSelectorsResponse
Prelude.Read, Int -> PutInsightSelectorsResponse -> ShowS
[PutInsightSelectorsResponse] -> ShowS
PutInsightSelectorsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutInsightSelectorsResponse] -> ShowS
$cshowList :: [PutInsightSelectorsResponse] -> ShowS
show :: PutInsightSelectorsResponse -> String
$cshow :: PutInsightSelectorsResponse -> String
showsPrec :: Int -> PutInsightSelectorsResponse -> ShowS
$cshowsPrec :: Int -> PutInsightSelectorsResponse -> ShowS
Prelude.Show, forall x.
Rep PutInsightSelectorsResponse x -> PutInsightSelectorsResponse
forall x.
PutInsightSelectorsResponse -> Rep PutInsightSelectorsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutInsightSelectorsResponse x -> PutInsightSelectorsResponse
$cfrom :: forall x.
PutInsightSelectorsResponse -> Rep PutInsightSelectorsResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutInsightSelectorsResponse' 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:
--
-- 'insightSelectors', 'putInsightSelectorsResponse_insightSelectors' - A JSON string that contains the Insights event types that you want to
-- log on a trail. The valid Insights types in this release are
-- @ApiErrorRateInsight@ and @ApiCallRateInsight@.
--
-- 'trailARN', 'putInsightSelectorsResponse_trailARN' - The Amazon Resource Name (ARN) of a trail for which you want to change
-- or add Insights selectors.
--
-- 'httpStatus', 'putInsightSelectorsResponse_httpStatus' - The response's http status code.
newPutInsightSelectorsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutInsightSelectorsResponse
newPutInsightSelectorsResponse :: Int -> PutInsightSelectorsResponse
newPutInsightSelectorsResponse Int
pHttpStatus_ =
  PutInsightSelectorsResponse'
    { $sel:insightSelectors:PutInsightSelectorsResponse' :: Maybe [InsightSelector]
insightSelectors =
        forall a. Maybe a
Prelude.Nothing,
      $sel:trailARN:PutInsightSelectorsResponse' :: Maybe Text
trailARN = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutInsightSelectorsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A JSON string that contains the Insights event types that you want to
-- log on a trail. The valid Insights types in this release are
-- @ApiErrorRateInsight@ and @ApiCallRateInsight@.
putInsightSelectorsResponse_insightSelectors :: Lens.Lens' PutInsightSelectorsResponse (Prelude.Maybe [InsightSelector])
putInsightSelectorsResponse_insightSelectors :: Lens' PutInsightSelectorsResponse (Maybe [InsightSelector])
putInsightSelectorsResponse_insightSelectors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightSelectorsResponse' {Maybe [InsightSelector]
insightSelectors :: Maybe [InsightSelector]
$sel:insightSelectors:PutInsightSelectorsResponse' :: PutInsightSelectorsResponse -> Maybe [InsightSelector]
insightSelectors} -> Maybe [InsightSelector]
insightSelectors) (\s :: PutInsightSelectorsResponse
s@PutInsightSelectorsResponse' {} Maybe [InsightSelector]
a -> PutInsightSelectorsResponse
s {$sel:insightSelectors:PutInsightSelectorsResponse' :: Maybe [InsightSelector]
insightSelectors = Maybe [InsightSelector]
a} :: PutInsightSelectorsResponse) 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 Amazon Resource Name (ARN) of a trail for which you want to change
-- or add Insights selectors.
putInsightSelectorsResponse_trailARN :: Lens.Lens' PutInsightSelectorsResponse (Prelude.Maybe Prelude.Text)
putInsightSelectorsResponse_trailARN :: Lens' PutInsightSelectorsResponse (Maybe Text)
putInsightSelectorsResponse_trailARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightSelectorsResponse' {Maybe Text
trailARN :: Maybe Text
$sel:trailARN:PutInsightSelectorsResponse' :: PutInsightSelectorsResponse -> Maybe Text
trailARN} -> Maybe Text
trailARN) (\s :: PutInsightSelectorsResponse
s@PutInsightSelectorsResponse' {} Maybe Text
a -> PutInsightSelectorsResponse
s {$sel:trailARN:PutInsightSelectorsResponse' :: Maybe Text
trailARN = Maybe Text
a} :: PutInsightSelectorsResponse)

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

instance Prelude.NFData PutInsightSelectorsResponse where
  rnf :: PutInsightSelectorsResponse -> ()
rnf PutInsightSelectorsResponse' {Int
Maybe [InsightSelector]
Maybe Text
httpStatus :: Int
trailARN :: Maybe Text
insightSelectors :: Maybe [InsightSelector]
$sel:httpStatus:PutInsightSelectorsResponse' :: PutInsightSelectorsResponse -> Int
$sel:trailARN:PutInsightSelectorsResponse' :: PutInsightSelectorsResponse -> Maybe Text
$sel:insightSelectors:PutInsightSelectorsResponse' :: PutInsightSelectorsResponse -> Maybe [InsightSelector]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [InsightSelector]
insightSelectors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
trailARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus