{-# 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.IoT.ReplaceTopicRule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Replaces the rule. You must specify all parameters for the new rule.
-- Creating rules is an administrator-level action. Any user who has
-- permission to create rules will be able to access data processed by the
-- rule.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions ReplaceTopicRule>
-- action.
module Amazonka.IoT.ReplaceTopicRule
  ( -- * Creating a Request
    ReplaceTopicRule (..),
    newReplaceTopicRule,

    -- * Request Lenses
    replaceTopicRule_ruleName,
    replaceTopicRule_topicRulePayload,

    -- * Destructuring the Response
    ReplaceTopicRuleResponse (..),
    newReplaceTopicRuleResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoT.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The input for the ReplaceTopicRule operation.
--
-- /See:/ 'newReplaceTopicRule' smart constructor.
data ReplaceTopicRule = ReplaceTopicRule'
  { -- | The name of the rule.
    ReplaceTopicRule -> Text
ruleName :: Prelude.Text,
    -- | The rule payload.
    ReplaceTopicRule -> TopicRulePayload
topicRulePayload :: TopicRulePayload
  }
  deriving (ReplaceTopicRule -> ReplaceTopicRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplaceTopicRule -> ReplaceTopicRule -> Bool
$c/= :: ReplaceTopicRule -> ReplaceTopicRule -> Bool
== :: ReplaceTopicRule -> ReplaceTopicRule -> Bool
$c== :: ReplaceTopicRule -> ReplaceTopicRule -> Bool
Prelude.Eq, ReadPrec [ReplaceTopicRule]
ReadPrec ReplaceTopicRule
Int -> ReadS ReplaceTopicRule
ReadS [ReplaceTopicRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReplaceTopicRule]
$creadListPrec :: ReadPrec [ReplaceTopicRule]
readPrec :: ReadPrec ReplaceTopicRule
$creadPrec :: ReadPrec ReplaceTopicRule
readList :: ReadS [ReplaceTopicRule]
$creadList :: ReadS [ReplaceTopicRule]
readsPrec :: Int -> ReadS ReplaceTopicRule
$creadsPrec :: Int -> ReadS ReplaceTopicRule
Prelude.Read, Int -> ReplaceTopicRule -> ShowS
[ReplaceTopicRule] -> ShowS
ReplaceTopicRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplaceTopicRule] -> ShowS
$cshowList :: [ReplaceTopicRule] -> ShowS
show :: ReplaceTopicRule -> String
$cshow :: ReplaceTopicRule -> String
showsPrec :: Int -> ReplaceTopicRule -> ShowS
$cshowsPrec :: Int -> ReplaceTopicRule -> ShowS
Prelude.Show, forall x. Rep ReplaceTopicRule x -> ReplaceTopicRule
forall x. ReplaceTopicRule -> Rep ReplaceTopicRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReplaceTopicRule x -> ReplaceTopicRule
$cfrom :: forall x. ReplaceTopicRule -> Rep ReplaceTopicRule x
Prelude.Generic)

-- |
-- Create a value of 'ReplaceTopicRule' 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:
--
-- 'ruleName', 'replaceTopicRule_ruleName' - The name of the rule.
--
-- 'topicRulePayload', 'replaceTopicRule_topicRulePayload' - The rule payload.
newReplaceTopicRule ::
  -- | 'ruleName'
  Prelude.Text ->
  -- | 'topicRulePayload'
  TopicRulePayload ->
  ReplaceTopicRule
newReplaceTopicRule :: Text -> TopicRulePayload -> ReplaceTopicRule
newReplaceTopicRule Text
pRuleName_ TopicRulePayload
pTopicRulePayload_ =
  ReplaceTopicRule'
    { $sel:ruleName:ReplaceTopicRule' :: Text
ruleName = Text
pRuleName_,
      $sel:topicRulePayload:ReplaceTopicRule' :: TopicRulePayload
topicRulePayload = TopicRulePayload
pTopicRulePayload_
    }

-- | The name of the rule.
replaceTopicRule_ruleName :: Lens.Lens' ReplaceTopicRule Prelude.Text
replaceTopicRule_ruleName :: Lens' ReplaceTopicRule Text
replaceTopicRule_ruleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplaceTopicRule' {Text
ruleName :: Text
$sel:ruleName:ReplaceTopicRule' :: ReplaceTopicRule -> Text
ruleName} -> Text
ruleName) (\s :: ReplaceTopicRule
s@ReplaceTopicRule' {} Text
a -> ReplaceTopicRule
s {$sel:ruleName:ReplaceTopicRule' :: Text
ruleName = Text
a} :: ReplaceTopicRule)

-- | The rule payload.
replaceTopicRule_topicRulePayload :: Lens.Lens' ReplaceTopicRule TopicRulePayload
replaceTopicRule_topicRulePayload :: Lens' ReplaceTopicRule TopicRulePayload
replaceTopicRule_topicRulePayload = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplaceTopicRule' {TopicRulePayload
topicRulePayload :: TopicRulePayload
$sel:topicRulePayload:ReplaceTopicRule' :: ReplaceTopicRule -> TopicRulePayload
topicRulePayload} -> TopicRulePayload
topicRulePayload) (\s :: ReplaceTopicRule
s@ReplaceTopicRule' {} TopicRulePayload
a -> ReplaceTopicRule
s {$sel:topicRulePayload:ReplaceTopicRule' :: TopicRulePayload
topicRulePayload = TopicRulePayload
a} :: ReplaceTopicRule)

instance Core.AWSRequest ReplaceTopicRule where
  type
    AWSResponse ReplaceTopicRule =
      ReplaceTopicRuleResponse
  request :: (Service -> Service)
-> ReplaceTopicRule -> Request ReplaceTopicRule
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ReplaceTopicRule
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ReplaceTopicRule)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull ReplaceTopicRuleResponse
ReplaceTopicRuleResponse'

instance Prelude.Hashable ReplaceTopicRule where
  hashWithSalt :: Int -> ReplaceTopicRule -> Int
hashWithSalt Int
_salt ReplaceTopicRule' {Text
TopicRulePayload
topicRulePayload :: TopicRulePayload
ruleName :: Text
$sel:topicRulePayload:ReplaceTopicRule' :: ReplaceTopicRule -> TopicRulePayload
$sel:ruleName:ReplaceTopicRule' :: ReplaceTopicRule -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TopicRulePayload
topicRulePayload

instance Prelude.NFData ReplaceTopicRule where
  rnf :: ReplaceTopicRule -> ()
rnf ReplaceTopicRule' {Text
TopicRulePayload
topicRulePayload :: TopicRulePayload
ruleName :: Text
$sel:topicRulePayload:ReplaceTopicRule' :: ReplaceTopicRule -> TopicRulePayload
$sel:ruleName:ReplaceTopicRule' :: ReplaceTopicRule -> Text
..} =
    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 TopicRulePayload
topicRulePayload

instance Data.ToHeaders ReplaceTopicRule where
  toHeaders :: ReplaceTopicRule -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON ReplaceTopicRule where
  toJSON :: ReplaceTopicRule -> Value
toJSON ReplaceTopicRule' {Text
TopicRulePayload
topicRulePayload :: TopicRulePayload
ruleName :: Text
$sel:topicRulePayload:ReplaceTopicRule' :: ReplaceTopicRule -> TopicRulePayload
$sel:ruleName:ReplaceTopicRule' :: ReplaceTopicRule -> Text
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON TopicRulePayload
topicRulePayload

instance Data.ToPath ReplaceTopicRule where
  toPath :: ReplaceTopicRule -> ByteString
toPath ReplaceTopicRule' {Text
TopicRulePayload
topicRulePayload :: TopicRulePayload
ruleName :: Text
$sel:topicRulePayload:ReplaceTopicRule' :: ReplaceTopicRule -> TopicRulePayload
$sel:ruleName:ReplaceTopicRule' :: ReplaceTopicRule -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/rules/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
ruleName]

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

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

-- |
-- Create a value of 'ReplaceTopicRuleResponse' 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.
newReplaceTopicRuleResponse ::
  ReplaceTopicRuleResponse
newReplaceTopicRuleResponse :: ReplaceTopicRuleResponse
newReplaceTopicRuleResponse =
  ReplaceTopicRuleResponse
ReplaceTopicRuleResponse'

instance Prelude.NFData ReplaceTopicRuleResponse where
  rnf :: ReplaceTopicRuleResponse -> ()
rnf ReplaceTopicRuleResponse
_ = ()