{-# 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.CloudWatch.PutManagedInsightRules
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a managed Contributor Insights rule for a specified Amazon Web
-- Services resource. When you enable a managed rule, you create a
-- Contributor Insights rule that collects data from Amazon Web Services
-- services. You cannot edit these rules with @PutInsightRule@. The rules
-- can be enabled, disabled, and deleted using @EnableInsightRules@,
-- @DisableInsightRules@, and @DeleteInsightRules@. If a previously created
-- managed rule is currently disabled, a subsequent call to this API will
-- re-enable it. Use @ListManagedInsightRules@ to describe all available
-- rules.
module Amazonka.CloudWatch.PutManagedInsightRules
  ( -- * Creating a Request
    PutManagedInsightRules (..),
    newPutManagedInsightRules,

    -- * Request Lenses
    putManagedInsightRules_managedRules,

    -- * Destructuring the Response
    PutManagedInsightRulesResponse (..),
    newPutManagedInsightRulesResponse,

    -- * Response Lenses
    putManagedInsightRulesResponse_failures,
    putManagedInsightRulesResponse_httpStatus,
  )
where

import Amazonka.CloudWatch.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:/ 'newPutManagedInsightRules' smart constructor.
data PutManagedInsightRules = PutManagedInsightRules'
  { -- | A list of @ManagedRules@ to enable.
    PutManagedInsightRules -> [ManagedRule]
managedRules :: [ManagedRule]
  }
  deriving (PutManagedInsightRules -> PutManagedInsightRules -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutManagedInsightRules -> PutManagedInsightRules -> Bool
$c/= :: PutManagedInsightRules -> PutManagedInsightRules -> Bool
== :: PutManagedInsightRules -> PutManagedInsightRules -> Bool
$c== :: PutManagedInsightRules -> PutManagedInsightRules -> Bool
Prelude.Eq, ReadPrec [PutManagedInsightRules]
ReadPrec PutManagedInsightRules
Int -> ReadS PutManagedInsightRules
ReadS [PutManagedInsightRules]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutManagedInsightRules]
$creadListPrec :: ReadPrec [PutManagedInsightRules]
readPrec :: ReadPrec PutManagedInsightRules
$creadPrec :: ReadPrec PutManagedInsightRules
readList :: ReadS [PutManagedInsightRules]
$creadList :: ReadS [PutManagedInsightRules]
readsPrec :: Int -> ReadS PutManagedInsightRules
$creadsPrec :: Int -> ReadS PutManagedInsightRules
Prelude.Read, Int -> PutManagedInsightRules -> ShowS
[PutManagedInsightRules] -> ShowS
PutManagedInsightRules -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutManagedInsightRules] -> ShowS
$cshowList :: [PutManagedInsightRules] -> ShowS
show :: PutManagedInsightRules -> String
$cshow :: PutManagedInsightRules -> String
showsPrec :: Int -> PutManagedInsightRules -> ShowS
$cshowsPrec :: Int -> PutManagedInsightRules -> ShowS
Prelude.Show, forall x. Rep PutManagedInsightRules x -> PutManagedInsightRules
forall x. PutManagedInsightRules -> Rep PutManagedInsightRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutManagedInsightRules x -> PutManagedInsightRules
$cfrom :: forall x. PutManagedInsightRules -> Rep PutManagedInsightRules x
Prelude.Generic)

-- |
-- Create a value of 'PutManagedInsightRules' 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:
--
-- 'managedRules', 'putManagedInsightRules_managedRules' - A list of @ManagedRules@ to enable.
newPutManagedInsightRules ::
  PutManagedInsightRules
newPutManagedInsightRules :: PutManagedInsightRules
newPutManagedInsightRules =
  PutManagedInsightRules'
    { $sel:managedRules:PutManagedInsightRules' :: [ManagedRule]
managedRules =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | A list of @ManagedRules@ to enable.
putManagedInsightRules_managedRules :: Lens.Lens' PutManagedInsightRules [ManagedRule]
putManagedInsightRules_managedRules :: Lens' PutManagedInsightRules [ManagedRule]
putManagedInsightRules_managedRules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutManagedInsightRules' {[ManagedRule]
managedRules :: [ManagedRule]
$sel:managedRules:PutManagedInsightRules' :: PutManagedInsightRules -> [ManagedRule]
managedRules} -> [ManagedRule]
managedRules) (\s :: PutManagedInsightRules
s@PutManagedInsightRules' {} [ManagedRule]
a -> PutManagedInsightRules
s {$sel:managedRules:PutManagedInsightRules' :: [ManagedRule]
managedRules = [ManagedRule]
a} :: PutManagedInsightRules) 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 PutManagedInsightRules where
  type
    AWSResponse PutManagedInsightRules =
      PutManagedInsightRulesResponse
  request :: (Service -> Service)
-> PutManagedInsightRules -> Request PutManagedInsightRules
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy PutManagedInsightRules
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutManagedInsightRules)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"PutManagedInsightRulesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [PartialFailure] -> Int -> PutManagedInsightRulesResponse
PutManagedInsightRulesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Failures"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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 PutManagedInsightRules where
  hashWithSalt :: Int -> PutManagedInsightRules -> Int
hashWithSalt Int
_salt PutManagedInsightRules' {[ManagedRule]
managedRules :: [ManagedRule]
$sel:managedRules:PutManagedInsightRules' :: PutManagedInsightRules -> [ManagedRule]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [ManagedRule]
managedRules

instance Prelude.NFData PutManagedInsightRules where
  rnf :: PutManagedInsightRules -> ()
rnf PutManagedInsightRules' {[ManagedRule]
managedRules :: [ManagedRule]
$sel:managedRules:PutManagedInsightRules' :: PutManagedInsightRules -> [ManagedRule]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [ManagedRule]
managedRules

instance Data.ToHeaders PutManagedInsightRules where
  toHeaders :: PutManagedInsightRules -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery PutManagedInsightRules where
  toQuery :: PutManagedInsightRules -> QueryString
toQuery PutManagedInsightRules' {[ManagedRule]
managedRules :: [ManagedRule]
$sel:managedRules:PutManagedInsightRules' :: PutManagedInsightRules -> [ManagedRule]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"PutManagedInsightRules" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-08-01" :: Prelude.ByteString),
        ByteString
"ManagedRules"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [ManagedRule]
managedRules
      ]

-- | /See:/ 'newPutManagedInsightRulesResponse' smart constructor.
data PutManagedInsightRulesResponse = PutManagedInsightRulesResponse'
  { -- | An array that lists the rules that could not be enabled.
    PutManagedInsightRulesResponse -> Maybe [PartialFailure]
failures :: Prelude.Maybe [PartialFailure],
    -- | The response's http status code.
    PutManagedInsightRulesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PutManagedInsightRulesResponse
-> PutManagedInsightRulesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutManagedInsightRulesResponse
-> PutManagedInsightRulesResponse -> Bool
$c/= :: PutManagedInsightRulesResponse
-> PutManagedInsightRulesResponse -> Bool
== :: PutManagedInsightRulesResponse
-> PutManagedInsightRulesResponse -> Bool
$c== :: PutManagedInsightRulesResponse
-> PutManagedInsightRulesResponse -> Bool
Prelude.Eq, ReadPrec [PutManagedInsightRulesResponse]
ReadPrec PutManagedInsightRulesResponse
Int -> ReadS PutManagedInsightRulesResponse
ReadS [PutManagedInsightRulesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutManagedInsightRulesResponse]
$creadListPrec :: ReadPrec [PutManagedInsightRulesResponse]
readPrec :: ReadPrec PutManagedInsightRulesResponse
$creadPrec :: ReadPrec PutManagedInsightRulesResponse
readList :: ReadS [PutManagedInsightRulesResponse]
$creadList :: ReadS [PutManagedInsightRulesResponse]
readsPrec :: Int -> ReadS PutManagedInsightRulesResponse
$creadsPrec :: Int -> ReadS PutManagedInsightRulesResponse
Prelude.Read, Int -> PutManagedInsightRulesResponse -> ShowS
[PutManagedInsightRulesResponse] -> ShowS
PutManagedInsightRulesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutManagedInsightRulesResponse] -> ShowS
$cshowList :: [PutManagedInsightRulesResponse] -> ShowS
show :: PutManagedInsightRulesResponse -> String
$cshow :: PutManagedInsightRulesResponse -> String
showsPrec :: Int -> PutManagedInsightRulesResponse -> ShowS
$cshowsPrec :: Int -> PutManagedInsightRulesResponse -> ShowS
Prelude.Show, forall x.
Rep PutManagedInsightRulesResponse x
-> PutManagedInsightRulesResponse
forall x.
PutManagedInsightRulesResponse
-> Rep PutManagedInsightRulesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutManagedInsightRulesResponse x
-> PutManagedInsightRulesResponse
$cfrom :: forall x.
PutManagedInsightRulesResponse
-> Rep PutManagedInsightRulesResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutManagedInsightRulesResponse' 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:
--
-- 'failures', 'putManagedInsightRulesResponse_failures' - An array that lists the rules that could not be enabled.
--
-- 'httpStatus', 'putManagedInsightRulesResponse_httpStatus' - The response's http status code.
newPutManagedInsightRulesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutManagedInsightRulesResponse
newPutManagedInsightRulesResponse :: Int -> PutManagedInsightRulesResponse
newPutManagedInsightRulesResponse Int
pHttpStatus_ =
  PutManagedInsightRulesResponse'
    { $sel:failures:PutManagedInsightRulesResponse' :: Maybe [PartialFailure]
failures =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutManagedInsightRulesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array that lists the rules that could not be enabled.
putManagedInsightRulesResponse_failures :: Lens.Lens' PutManagedInsightRulesResponse (Prelude.Maybe [PartialFailure])
putManagedInsightRulesResponse_failures :: Lens' PutManagedInsightRulesResponse (Maybe [PartialFailure])
putManagedInsightRulesResponse_failures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutManagedInsightRulesResponse' {Maybe [PartialFailure]
failures :: Maybe [PartialFailure]
$sel:failures:PutManagedInsightRulesResponse' :: PutManagedInsightRulesResponse -> Maybe [PartialFailure]
failures} -> Maybe [PartialFailure]
failures) (\s :: PutManagedInsightRulesResponse
s@PutManagedInsightRulesResponse' {} Maybe [PartialFailure]
a -> PutManagedInsightRulesResponse
s {$sel:failures:PutManagedInsightRulesResponse' :: Maybe [PartialFailure]
failures = Maybe [PartialFailure]
a} :: PutManagedInsightRulesResponse) 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.
putManagedInsightRulesResponse_httpStatus :: Lens.Lens' PutManagedInsightRulesResponse Prelude.Int
putManagedInsightRulesResponse_httpStatus :: Lens' PutManagedInsightRulesResponse Int
putManagedInsightRulesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutManagedInsightRulesResponse' {Int
httpStatus :: Int
$sel:httpStatus:PutManagedInsightRulesResponse' :: PutManagedInsightRulesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: PutManagedInsightRulesResponse
s@PutManagedInsightRulesResponse' {} Int
a -> PutManagedInsightRulesResponse
s {$sel:httpStatus:PutManagedInsightRulesResponse' :: Int
httpStatus = Int
a} :: PutManagedInsightRulesResponse)

instance
  Prelude.NFData
    PutManagedInsightRulesResponse
  where
  rnf :: PutManagedInsightRulesResponse -> ()
rnf PutManagedInsightRulesResponse' {Int
Maybe [PartialFailure]
httpStatus :: Int
failures :: Maybe [PartialFailure]
$sel:httpStatus:PutManagedInsightRulesResponse' :: PutManagedInsightRulesResponse -> Int
$sel:failures:PutManagedInsightRulesResponse' :: PutManagedInsightRulesResponse -> Maybe [PartialFailure]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [PartialFailure]
failures
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus