{-# 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.CloudWatchEvents.EnableRule
-- 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 the specified rule. If the rule does not exist, the operation
-- fails.
--
-- When you enable a rule, incoming events might not immediately start
-- matching to a newly enabled rule. Allow a short period of time for
-- changes to take effect.
module Amazonka.CloudWatchEvents.EnableRule
  ( -- * Creating a Request
    EnableRule (..),
    newEnableRule,

    -- * Request Lenses
    enableRule_eventBusName,
    enableRule_name,

    -- * Destructuring the Response
    EnableRuleResponse (..),
    newEnableRuleResponse,
  )
where

import Amazonka.CloudWatchEvents.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:/ 'newEnableRule' smart constructor.
data EnableRule = EnableRule'
  { -- | The name or ARN of the event bus associated with the rule. If you omit
    -- this, the default event bus is used.
    EnableRule -> Maybe Text
eventBusName :: Prelude.Maybe Prelude.Text,
    -- | The name of the rule.
    EnableRule -> Text
name :: Prelude.Text
  }
  deriving (EnableRule -> EnableRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableRule -> EnableRule -> Bool
$c/= :: EnableRule -> EnableRule -> Bool
== :: EnableRule -> EnableRule -> Bool
$c== :: EnableRule -> EnableRule -> Bool
Prelude.Eq, ReadPrec [EnableRule]
ReadPrec EnableRule
Int -> ReadS EnableRule
ReadS [EnableRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableRule]
$creadListPrec :: ReadPrec [EnableRule]
readPrec :: ReadPrec EnableRule
$creadPrec :: ReadPrec EnableRule
readList :: ReadS [EnableRule]
$creadList :: ReadS [EnableRule]
readsPrec :: Int -> ReadS EnableRule
$creadsPrec :: Int -> ReadS EnableRule
Prelude.Read, Int -> EnableRule -> ShowS
[EnableRule] -> ShowS
EnableRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableRule] -> ShowS
$cshowList :: [EnableRule] -> ShowS
show :: EnableRule -> String
$cshow :: EnableRule -> String
showsPrec :: Int -> EnableRule -> ShowS
$cshowsPrec :: Int -> EnableRule -> ShowS
Prelude.Show, forall x. Rep EnableRule x -> EnableRule
forall x. EnableRule -> Rep EnableRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableRule x -> EnableRule
$cfrom :: forall x. EnableRule -> Rep EnableRule x
Prelude.Generic)

-- |
-- Create a value of 'EnableRule' 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:
--
-- 'eventBusName', 'enableRule_eventBusName' - The name or ARN of the event bus associated with the rule. If you omit
-- this, the default event bus is used.
--
-- 'name', 'enableRule_name' - The name of the rule.
newEnableRule ::
  -- | 'name'
  Prelude.Text ->
  EnableRule
newEnableRule :: Text -> EnableRule
newEnableRule Text
pName_ =
  EnableRule'
    { $sel:eventBusName:EnableRule' :: Maybe Text
eventBusName = forall a. Maybe a
Prelude.Nothing,
      $sel:name:EnableRule' :: Text
name = Text
pName_
    }

-- | The name or ARN of the event bus associated with the rule. If you omit
-- this, the default event bus is used.
enableRule_eventBusName :: Lens.Lens' EnableRule (Prelude.Maybe Prelude.Text)
enableRule_eventBusName :: Lens' EnableRule (Maybe Text)
enableRule_eventBusName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableRule' {Maybe Text
eventBusName :: Maybe Text
$sel:eventBusName:EnableRule' :: EnableRule -> Maybe Text
eventBusName} -> Maybe Text
eventBusName) (\s :: EnableRule
s@EnableRule' {} Maybe Text
a -> EnableRule
s {$sel:eventBusName:EnableRule' :: Maybe Text
eventBusName = Maybe Text
a} :: EnableRule)

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

instance Core.AWSRequest EnableRule where
  type AWSResponse EnableRule = EnableRuleResponse
  request :: (Service -> Service) -> EnableRule -> Request EnableRule
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 EnableRule
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse EnableRule)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull EnableRuleResponse
EnableRuleResponse'

instance Prelude.Hashable EnableRule where
  hashWithSalt :: Int -> EnableRule -> Int
hashWithSalt Int
_salt EnableRule' {Maybe Text
Text
name :: Text
eventBusName :: Maybe Text
$sel:name:EnableRule' :: EnableRule -> Text
$sel:eventBusName:EnableRule' :: EnableRule -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
eventBusName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData EnableRule where
  rnf :: EnableRule -> ()
rnf EnableRule' {Maybe Text
Text
name :: Text
eventBusName :: Maybe Text
$sel:name:EnableRule' :: EnableRule -> Text
$sel:eventBusName:EnableRule' :: EnableRule -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eventBusName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders EnableRule where
  toHeaders :: EnableRule -> [Header]
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 -> [Header]
Data.=# (ByteString
"AWSEvents.EnableRule" :: Prelude.ByteString),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON EnableRule where
  toJSON :: EnableRule -> Value
toJSON EnableRule' {Maybe Text
Text
name :: Text
eventBusName :: Maybe Text
$sel:name:EnableRule' :: EnableRule -> Text
$sel:eventBusName:EnableRule' :: EnableRule -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"EventBusName" 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
eventBusName,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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

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

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

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

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