{-# 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.CodeStarNotifications.Subscribe
-- 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 an association between a notification rule and an Chatbot topic
-- or Chatbot client so that the associated target can receive
-- notifications when the events described in the rule are triggered.
module Amazonka.CodeStarNotifications.Subscribe
  ( -- * Creating a Request
    Subscribe (..),
    newSubscribe,

    -- * Request Lenses
    subscribe_clientRequestToken,
    subscribe_arn,
    subscribe_target,

    -- * Destructuring the Response
    SubscribeResponse (..),
    newSubscribeResponse,

    -- * Response Lenses
    subscribeResponse_arn,
    subscribeResponse_httpStatus,
  )
where

import Amazonka.CodeStarNotifications.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:/ 'newSubscribe' smart constructor.
data Subscribe = Subscribe'
  { -- | An enumeration token that, when provided in a request, returns the next
    -- batch of the results.
    Subscribe -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the notification rule for which you
    -- want to create the association.
    Subscribe -> Text
arn :: Prelude.Text,
    Subscribe -> Target
target :: Target
  }
  deriving (Subscribe -> Subscribe -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subscribe -> Subscribe -> Bool
$c/= :: Subscribe -> Subscribe -> Bool
== :: Subscribe -> Subscribe -> Bool
$c== :: Subscribe -> Subscribe -> Bool
Prelude.Eq, Int -> Subscribe -> ShowS
[Subscribe] -> ShowS
Subscribe -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subscribe] -> ShowS
$cshowList :: [Subscribe] -> ShowS
show :: Subscribe -> String
$cshow :: Subscribe -> String
showsPrec :: Int -> Subscribe -> ShowS
$cshowsPrec :: Int -> Subscribe -> ShowS
Prelude.Show, forall x. Rep Subscribe x -> Subscribe
forall x. Subscribe -> Rep Subscribe x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Subscribe x -> Subscribe
$cfrom :: forall x. Subscribe -> Rep Subscribe x
Prelude.Generic)

-- |
-- Create a value of 'Subscribe' 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:
--
-- 'clientRequestToken', 'subscribe_clientRequestToken' - An enumeration token that, when provided in a request, returns the next
-- batch of the results.
--
-- 'arn', 'subscribe_arn' - The Amazon Resource Name (ARN) of the notification rule for which you
-- want to create the association.
--
-- 'target', 'subscribe_target' - Undocumented member.
newSubscribe ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'target'
  Target ->
  Subscribe
newSubscribe :: Text -> Target -> Subscribe
newSubscribe Text
pArn_ Target
pTarget_ =
  Subscribe'
    { $sel:clientRequestToken:Subscribe' :: Maybe Text
clientRequestToken = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:Subscribe' :: Text
arn = Text
pArn_,
      $sel:target:Subscribe' :: Target
target = Target
pTarget_
    }

-- | An enumeration token that, when provided in a request, returns the next
-- batch of the results.
subscribe_clientRequestToken :: Lens.Lens' Subscribe (Prelude.Maybe Prelude.Text)
subscribe_clientRequestToken :: Lens' Subscribe (Maybe Text)
subscribe_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:Subscribe' :: Subscribe -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: Subscribe
s@Subscribe' {} Maybe Text
a -> Subscribe
s {$sel:clientRequestToken:Subscribe' :: Maybe Text
clientRequestToken = Maybe Text
a} :: Subscribe)

-- | The Amazon Resource Name (ARN) of the notification rule for which you
-- want to create the association.
subscribe_arn :: Lens.Lens' Subscribe Prelude.Text
subscribe_arn :: Lens' Subscribe Text
subscribe_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Text
arn :: Text
$sel:arn:Subscribe' :: Subscribe -> Text
arn} -> Text
arn) (\s :: Subscribe
s@Subscribe' {} Text
a -> Subscribe
s {$sel:arn:Subscribe' :: Text
arn = Text
a} :: Subscribe)

-- | Undocumented member.
subscribe_target :: Lens.Lens' Subscribe Target
subscribe_target :: Lens' Subscribe Target
subscribe_target = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Target
target :: Target
$sel:target:Subscribe' :: Subscribe -> Target
target} -> Target
target) (\s :: Subscribe
s@Subscribe' {} Target
a -> Subscribe
s {$sel:target:Subscribe' :: Target
target = Target
a} :: Subscribe)

instance Core.AWSRequest Subscribe where
  type AWSResponse Subscribe = SubscribeResponse
  request :: (Service -> Service) -> Subscribe -> Request Subscribe
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 Subscribe
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse Subscribe)))
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 Text -> Int -> SubscribeResponse
SubscribeResponse'
            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
"Arn")
            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 Subscribe where
  hashWithSalt :: Int -> Subscribe -> Int
hashWithSalt Int
_salt Subscribe' {Maybe Text
Text
Target
target :: Target
arn :: Text
clientRequestToken :: Maybe Text
$sel:target:Subscribe' :: Subscribe -> Target
$sel:arn:Subscribe' :: Subscribe -> Text
$sel:clientRequestToken:Subscribe' :: Subscribe -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Target
target

instance Prelude.NFData Subscribe where
  rnf :: Subscribe -> ()
rnf Subscribe' {Maybe Text
Text
Target
target :: Target
arn :: Text
clientRequestToken :: Maybe Text
$sel:target:Subscribe' :: Subscribe -> Target
$sel:arn:Subscribe' :: Subscribe -> Text
$sel:clientRequestToken:Subscribe' :: Subscribe -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Target
target

instance Data.ToHeaders Subscribe where
  toHeaders :: Subscribe -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON Subscribe where
  toJSON :: Subscribe -> Value
toJSON Subscribe' {Maybe Text
Text
Target
target :: Target
arn :: Text
clientRequestToken :: Maybe Text
$sel:target:Subscribe' :: Subscribe -> Target
$sel:arn:Subscribe' :: Subscribe -> Text
$sel:clientRequestToken:Subscribe' :: Subscribe -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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
clientRequestToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"Arn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
arn),
            forall a. a -> Maybe a
Prelude.Just (Key
"Target" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Target
target)
          ]
      )

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

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

-- | /See:/ 'newSubscribeResponse' smart constructor.
data SubscribeResponse = SubscribeResponse'
  { -- | The Amazon Resource Name (ARN) of the notification rule for which you
    -- have created assocations.
    SubscribeResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    SubscribeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SubscribeResponse -> SubscribeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscribeResponse -> SubscribeResponse -> Bool
$c/= :: SubscribeResponse -> SubscribeResponse -> Bool
== :: SubscribeResponse -> SubscribeResponse -> Bool
$c== :: SubscribeResponse -> SubscribeResponse -> Bool
Prelude.Eq, ReadPrec [SubscribeResponse]
ReadPrec SubscribeResponse
Int -> ReadS SubscribeResponse
ReadS [SubscribeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SubscribeResponse]
$creadListPrec :: ReadPrec [SubscribeResponse]
readPrec :: ReadPrec SubscribeResponse
$creadPrec :: ReadPrec SubscribeResponse
readList :: ReadS [SubscribeResponse]
$creadList :: ReadS [SubscribeResponse]
readsPrec :: Int -> ReadS SubscribeResponse
$creadsPrec :: Int -> ReadS SubscribeResponse
Prelude.Read, Int -> SubscribeResponse -> ShowS
[SubscribeResponse] -> ShowS
SubscribeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscribeResponse] -> ShowS
$cshowList :: [SubscribeResponse] -> ShowS
show :: SubscribeResponse -> String
$cshow :: SubscribeResponse -> String
showsPrec :: Int -> SubscribeResponse -> ShowS
$cshowsPrec :: Int -> SubscribeResponse -> ShowS
Prelude.Show, forall x. Rep SubscribeResponse x -> SubscribeResponse
forall x. SubscribeResponse -> Rep SubscribeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubscribeResponse x -> SubscribeResponse
$cfrom :: forall x. SubscribeResponse -> Rep SubscribeResponse x
Prelude.Generic)

-- |
-- Create a value of 'SubscribeResponse' 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:
--
-- 'arn', 'subscribeResponse_arn' - The Amazon Resource Name (ARN) of the notification rule for which you
-- have created assocations.
--
-- 'httpStatus', 'subscribeResponse_httpStatus' - The response's http status code.
newSubscribeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SubscribeResponse
newSubscribeResponse :: Int -> SubscribeResponse
newSubscribeResponse Int
pHttpStatus_ =
  SubscribeResponse'
    { $sel:arn:SubscribeResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SubscribeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the notification rule for which you
-- have created assocations.
subscribeResponse_arn :: Lens.Lens' SubscribeResponse (Prelude.Maybe Prelude.Text)
subscribeResponse_arn :: Lens' SubscribeResponse (Maybe Text)
subscribeResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SubscribeResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:SubscribeResponse' :: SubscribeResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: SubscribeResponse
s@SubscribeResponse' {} Maybe Text
a -> SubscribeResponse
s {$sel:arn:SubscribeResponse' :: Maybe Text
arn = Maybe Text
a} :: SubscribeResponse)

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

instance Prelude.NFData SubscribeResponse where
  rnf :: SubscribeResponse -> ()
rnf SubscribeResponse' {Int
Maybe Text
httpStatus :: Int
arn :: Maybe Text
$sel:httpStatus:SubscribeResponse' :: SubscribeResponse -> Int
$sel:arn:SubscribeResponse' :: SubscribeResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus