{-# 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.PutInsightRule
-- 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 Contributor Insights rule. Rules evaluate log events in a
-- CloudWatch Logs log group, enabling you to find contributor data for the
-- log events in that log group. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/ContributorInsights.html Using Contributor Insights to Analyze High-Cardinality Data>.
--
-- If you create a rule, delete it, and then re-create it with the same
-- name, historical data from the first time the rule was created might not
-- be available.
module Amazonka.CloudWatch.PutInsightRule
  ( -- * Creating a Request
    PutInsightRule (..),
    newPutInsightRule,

    -- * Request Lenses
    putInsightRule_ruleState,
    putInsightRule_tags,
    putInsightRule_ruleName,
    putInsightRule_ruleDefinition,

    -- * Destructuring the Response
    PutInsightRuleResponse (..),
    newPutInsightRuleResponse,

    -- * Response Lenses
    putInsightRuleResponse_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:/ 'newPutInsightRule' smart constructor.
data PutInsightRule = PutInsightRule'
  { -- | The state of the rule. Valid values are ENABLED and DISABLED.
    PutInsightRule -> Maybe Text
ruleState :: Prelude.Maybe Prelude.Text,
    -- | A list of key-value pairs to associate with the Contributor Insights
    -- rule. You can associate as many as 50 tags with a rule.
    --
    -- Tags can help you organize and categorize your resources. You can also
    -- use them to scope user permissions, by granting a user permission to
    -- access or change only the resources that have certain tag values.
    --
    -- To be able to associate tags with a rule, you must have the
    -- @cloudwatch:TagResource@ permission in addition to the
    -- @cloudwatch:PutInsightRule@ permission.
    --
    -- If you are using this operation to update an existing Contributor
    -- Insights rule, any tags you specify in this parameter are ignored. To
    -- change the tags of an existing rule, use
    -- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/APIReference/API_TagResource.html TagResource>.
    PutInsightRule -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A unique name for the rule.
    PutInsightRule -> Text
ruleName :: Prelude.Text,
    -- | The definition of the rule, as a JSON object. For details on the valid
    -- syntax, see
    -- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/ContributorInsights-RuleSyntax.html Contributor Insights Rule Syntax>.
    PutInsightRule -> Text
ruleDefinition :: Prelude.Text
  }
  deriving (PutInsightRule -> PutInsightRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutInsightRule -> PutInsightRule -> Bool
$c/= :: PutInsightRule -> PutInsightRule -> Bool
== :: PutInsightRule -> PutInsightRule -> Bool
$c== :: PutInsightRule -> PutInsightRule -> Bool
Prelude.Eq, ReadPrec [PutInsightRule]
ReadPrec PutInsightRule
Int -> ReadS PutInsightRule
ReadS [PutInsightRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutInsightRule]
$creadListPrec :: ReadPrec [PutInsightRule]
readPrec :: ReadPrec PutInsightRule
$creadPrec :: ReadPrec PutInsightRule
readList :: ReadS [PutInsightRule]
$creadList :: ReadS [PutInsightRule]
readsPrec :: Int -> ReadS PutInsightRule
$creadsPrec :: Int -> ReadS PutInsightRule
Prelude.Read, Int -> PutInsightRule -> ShowS
[PutInsightRule] -> ShowS
PutInsightRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutInsightRule] -> ShowS
$cshowList :: [PutInsightRule] -> ShowS
show :: PutInsightRule -> String
$cshow :: PutInsightRule -> String
showsPrec :: Int -> PutInsightRule -> ShowS
$cshowsPrec :: Int -> PutInsightRule -> ShowS
Prelude.Show, forall x. Rep PutInsightRule x -> PutInsightRule
forall x. PutInsightRule -> Rep PutInsightRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutInsightRule x -> PutInsightRule
$cfrom :: forall x. PutInsightRule -> Rep PutInsightRule x
Prelude.Generic)

-- |
-- Create a value of 'PutInsightRule' 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:
--
-- 'ruleState', 'putInsightRule_ruleState' - The state of the rule. Valid values are ENABLED and DISABLED.
--
-- 'tags', 'putInsightRule_tags' - A list of key-value pairs to associate with the Contributor Insights
-- rule. You can associate as many as 50 tags with a rule.
--
-- Tags can help you organize and categorize your resources. You can also
-- use them to scope user permissions, by granting a user permission to
-- access or change only the resources that have certain tag values.
--
-- To be able to associate tags with a rule, you must have the
-- @cloudwatch:TagResource@ permission in addition to the
-- @cloudwatch:PutInsightRule@ permission.
--
-- If you are using this operation to update an existing Contributor
-- Insights rule, any tags you specify in this parameter are ignored. To
-- change the tags of an existing rule, use
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/APIReference/API_TagResource.html TagResource>.
--
-- 'ruleName', 'putInsightRule_ruleName' - A unique name for the rule.
--
-- 'ruleDefinition', 'putInsightRule_ruleDefinition' - The definition of the rule, as a JSON object. For details on the valid
-- syntax, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/ContributorInsights-RuleSyntax.html Contributor Insights Rule Syntax>.
newPutInsightRule ::
  -- | 'ruleName'
  Prelude.Text ->
  -- | 'ruleDefinition'
  Prelude.Text ->
  PutInsightRule
newPutInsightRule :: Text -> Text -> PutInsightRule
newPutInsightRule Text
pRuleName_ Text
pRuleDefinition_ =
  PutInsightRule'
    { $sel:ruleState:PutInsightRule' :: Maybe Text
ruleState = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:PutInsightRule' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleName:PutInsightRule' :: Text
ruleName = Text
pRuleName_,
      $sel:ruleDefinition:PutInsightRule' :: Text
ruleDefinition = Text
pRuleDefinition_
    }

-- | The state of the rule. Valid values are ENABLED and DISABLED.
putInsightRule_ruleState :: Lens.Lens' PutInsightRule (Prelude.Maybe Prelude.Text)
putInsightRule_ruleState :: Lens' PutInsightRule (Maybe Text)
putInsightRule_ruleState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightRule' {Maybe Text
ruleState :: Maybe Text
$sel:ruleState:PutInsightRule' :: PutInsightRule -> Maybe Text
ruleState} -> Maybe Text
ruleState) (\s :: PutInsightRule
s@PutInsightRule' {} Maybe Text
a -> PutInsightRule
s {$sel:ruleState:PutInsightRule' :: Maybe Text
ruleState = Maybe Text
a} :: PutInsightRule)

-- | A list of key-value pairs to associate with the Contributor Insights
-- rule. You can associate as many as 50 tags with a rule.
--
-- Tags can help you organize and categorize your resources. You can also
-- use them to scope user permissions, by granting a user permission to
-- access or change only the resources that have certain tag values.
--
-- To be able to associate tags with a rule, you must have the
-- @cloudwatch:TagResource@ permission in addition to the
-- @cloudwatch:PutInsightRule@ permission.
--
-- If you are using this operation to update an existing Contributor
-- Insights rule, any tags you specify in this parameter are ignored. To
-- change the tags of an existing rule, use
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/APIReference/API_TagResource.html TagResource>.
putInsightRule_tags :: Lens.Lens' PutInsightRule (Prelude.Maybe [Tag])
putInsightRule_tags :: Lens' PutInsightRule (Maybe [Tag])
putInsightRule_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightRule' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:PutInsightRule' :: PutInsightRule -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: PutInsightRule
s@PutInsightRule' {} Maybe [Tag]
a -> PutInsightRule
s {$sel:tags:PutInsightRule' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: PutInsightRule) 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

-- | A unique name for the rule.
putInsightRule_ruleName :: Lens.Lens' PutInsightRule Prelude.Text
putInsightRule_ruleName :: Lens' PutInsightRule Text
putInsightRule_ruleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightRule' {Text
ruleName :: Text
$sel:ruleName:PutInsightRule' :: PutInsightRule -> Text
ruleName} -> Text
ruleName) (\s :: PutInsightRule
s@PutInsightRule' {} Text
a -> PutInsightRule
s {$sel:ruleName:PutInsightRule' :: Text
ruleName = Text
a} :: PutInsightRule)

-- | The definition of the rule, as a JSON object. For details on the valid
-- syntax, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/ContributorInsights-RuleSyntax.html Contributor Insights Rule Syntax>.
putInsightRule_ruleDefinition :: Lens.Lens' PutInsightRule Prelude.Text
putInsightRule_ruleDefinition :: Lens' PutInsightRule Text
putInsightRule_ruleDefinition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInsightRule' {Text
ruleDefinition :: Text
$sel:ruleDefinition:PutInsightRule' :: PutInsightRule -> Text
ruleDefinition} -> Text
ruleDefinition) (\s :: PutInsightRule
s@PutInsightRule' {} Text
a -> PutInsightRule
s {$sel:ruleDefinition:PutInsightRule' :: Text
ruleDefinition = Text
a} :: PutInsightRule)

instance Core.AWSRequest PutInsightRule where
  type
    AWSResponse PutInsightRule =
      PutInsightRuleResponse
  request :: (Service -> Service) -> PutInsightRule -> Request PutInsightRule
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 PutInsightRule
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutInsightRule)))
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
"PutInsightRuleResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> PutInsightRuleResponse
PutInsightRuleResponse'
            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 PutInsightRule where
  hashWithSalt :: Int -> PutInsightRule -> Int
hashWithSalt Int
_salt PutInsightRule' {Maybe [Tag]
Maybe Text
Text
ruleDefinition :: Text
ruleName :: Text
tags :: Maybe [Tag]
ruleState :: Maybe Text
$sel:ruleDefinition:PutInsightRule' :: PutInsightRule -> Text
$sel:ruleName:PutInsightRule' :: PutInsightRule -> Text
$sel:tags:PutInsightRule' :: PutInsightRule -> Maybe [Tag]
$sel:ruleState:PutInsightRule' :: PutInsightRule -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ruleState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleDefinition

instance Prelude.NFData PutInsightRule where
  rnf :: PutInsightRule -> ()
rnf PutInsightRule' {Maybe [Tag]
Maybe Text
Text
ruleDefinition :: Text
ruleName :: Text
tags :: Maybe [Tag]
ruleState :: Maybe Text
$sel:ruleDefinition:PutInsightRule' :: PutInsightRule -> Text
$sel:ruleName:PutInsightRule' :: PutInsightRule -> Text
$sel:tags:PutInsightRule' :: PutInsightRule -> Maybe [Tag]
$sel:ruleState:PutInsightRule' :: PutInsightRule -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ruleState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ruleName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ruleDefinition

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

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

instance Data.ToQuery PutInsightRule where
  toQuery :: PutInsightRule -> QueryString
toQuery PutInsightRule' {Maybe [Tag]
Maybe Text
Text
ruleDefinition :: Text
ruleName :: Text
tags :: Maybe [Tag]
ruleState :: Maybe Text
$sel:ruleDefinition:PutInsightRule' :: PutInsightRule -> Text
$sel:ruleName:PutInsightRule' :: PutInsightRule -> Text
$sel:tags:PutInsightRule' :: PutInsightRule -> Maybe [Tag]
$sel:ruleState:PutInsightRule' :: PutInsightRule -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"PutInsightRule" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-08-01" :: Prelude.ByteString),
        ByteString
"RuleState" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
ruleState,
        ByteString
"Tags"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags),
        ByteString
"RuleName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
ruleName,
        ByteString
"RuleDefinition" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
ruleDefinition
      ]

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

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

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

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