{-# 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.CodePipeline.RegisterWebhookWithThirdParty
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Configures a connection between the webhook that was created and the
-- external tool with events to be detected.
module Amazonka.CodePipeline.RegisterWebhookWithThirdParty
  ( -- * Creating a Request
    RegisterWebhookWithThirdParty (..),
    newRegisterWebhookWithThirdParty,

    -- * Request Lenses
    registerWebhookWithThirdParty_webhookName,

    -- * Destructuring the Response
    RegisterWebhookWithThirdPartyResponse (..),
    newRegisterWebhookWithThirdPartyResponse,

    -- * Response Lenses
    registerWebhookWithThirdPartyResponse_httpStatus,
  )
where

import Amazonka.CodePipeline.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:/ 'newRegisterWebhookWithThirdParty' smart constructor.
data RegisterWebhookWithThirdParty = RegisterWebhookWithThirdParty'
  { -- | The name of an existing webhook created with PutWebhook to register with
    -- a supported third party.
    RegisterWebhookWithThirdParty -> Maybe Text
webhookName :: Prelude.Maybe Prelude.Text
  }
  deriving (RegisterWebhookWithThirdParty
-> RegisterWebhookWithThirdParty -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterWebhookWithThirdParty
-> RegisterWebhookWithThirdParty -> Bool
$c/= :: RegisterWebhookWithThirdParty
-> RegisterWebhookWithThirdParty -> Bool
== :: RegisterWebhookWithThirdParty
-> RegisterWebhookWithThirdParty -> Bool
$c== :: RegisterWebhookWithThirdParty
-> RegisterWebhookWithThirdParty -> Bool
Prelude.Eq, ReadPrec [RegisterWebhookWithThirdParty]
ReadPrec RegisterWebhookWithThirdParty
Int -> ReadS RegisterWebhookWithThirdParty
ReadS [RegisterWebhookWithThirdParty]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterWebhookWithThirdParty]
$creadListPrec :: ReadPrec [RegisterWebhookWithThirdParty]
readPrec :: ReadPrec RegisterWebhookWithThirdParty
$creadPrec :: ReadPrec RegisterWebhookWithThirdParty
readList :: ReadS [RegisterWebhookWithThirdParty]
$creadList :: ReadS [RegisterWebhookWithThirdParty]
readsPrec :: Int -> ReadS RegisterWebhookWithThirdParty
$creadsPrec :: Int -> ReadS RegisterWebhookWithThirdParty
Prelude.Read, Int -> RegisterWebhookWithThirdParty -> ShowS
[RegisterWebhookWithThirdParty] -> ShowS
RegisterWebhookWithThirdParty -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterWebhookWithThirdParty] -> ShowS
$cshowList :: [RegisterWebhookWithThirdParty] -> ShowS
show :: RegisterWebhookWithThirdParty -> String
$cshow :: RegisterWebhookWithThirdParty -> String
showsPrec :: Int -> RegisterWebhookWithThirdParty -> ShowS
$cshowsPrec :: Int -> RegisterWebhookWithThirdParty -> ShowS
Prelude.Show, forall x.
Rep RegisterWebhookWithThirdParty x
-> RegisterWebhookWithThirdParty
forall x.
RegisterWebhookWithThirdParty
-> Rep RegisterWebhookWithThirdParty x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RegisterWebhookWithThirdParty x
-> RegisterWebhookWithThirdParty
$cfrom :: forall x.
RegisterWebhookWithThirdParty
-> Rep RegisterWebhookWithThirdParty x
Prelude.Generic)

-- |
-- Create a value of 'RegisterWebhookWithThirdParty' 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:
--
-- 'webhookName', 'registerWebhookWithThirdParty_webhookName' - The name of an existing webhook created with PutWebhook to register with
-- a supported third party.
newRegisterWebhookWithThirdParty ::
  RegisterWebhookWithThirdParty
newRegisterWebhookWithThirdParty :: RegisterWebhookWithThirdParty
newRegisterWebhookWithThirdParty =
  RegisterWebhookWithThirdParty'
    { $sel:webhookName:RegisterWebhookWithThirdParty' :: Maybe Text
webhookName =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The name of an existing webhook created with PutWebhook to register with
-- a supported third party.
registerWebhookWithThirdParty_webhookName :: Lens.Lens' RegisterWebhookWithThirdParty (Prelude.Maybe Prelude.Text)
registerWebhookWithThirdParty_webhookName :: Lens' RegisterWebhookWithThirdParty (Maybe Text)
registerWebhookWithThirdParty_webhookName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterWebhookWithThirdParty' {Maybe Text
webhookName :: Maybe Text
$sel:webhookName:RegisterWebhookWithThirdParty' :: RegisterWebhookWithThirdParty -> Maybe Text
webhookName} -> Maybe Text
webhookName) (\s :: RegisterWebhookWithThirdParty
s@RegisterWebhookWithThirdParty' {} Maybe Text
a -> RegisterWebhookWithThirdParty
s {$sel:webhookName:RegisterWebhookWithThirdParty' :: Maybe Text
webhookName = Maybe Text
a} :: RegisterWebhookWithThirdParty)

instance
  Core.AWSRequest
    RegisterWebhookWithThirdParty
  where
  type
    AWSResponse RegisterWebhookWithThirdParty =
      RegisterWebhookWithThirdPartyResponse
  request :: (Service -> Service)
-> RegisterWebhookWithThirdParty
-> Request RegisterWebhookWithThirdParty
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 RegisterWebhookWithThirdParty
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RegisterWebhookWithThirdParty)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> RegisterWebhookWithThirdPartyResponse
RegisterWebhookWithThirdPartyResponse'
            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
    RegisterWebhookWithThirdParty
  where
  hashWithSalt :: Int -> RegisterWebhookWithThirdParty -> Int
hashWithSalt Int
_salt RegisterWebhookWithThirdParty' {Maybe Text
webhookName :: Maybe Text
$sel:webhookName:RegisterWebhookWithThirdParty' :: RegisterWebhookWithThirdParty -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
webhookName

instance Prelude.NFData RegisterWebhookWithThirdParty where
  rnf :: RegisterWebhookWithThirdParty -> ()
rnf RegisterWebhookWithThirdParty' {Maybe Text
webhookName :: Maybe Text
$sel:webhookName:RegisterWebhookWithThirdParty' :: RegisterWebhookWithThirdParty -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
webhookName

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

instance Data.ToJSON RegisterWebhookWithThirdParty where
  toJSON :: RegisterWebhookWithThirdParty -> Value
toJSON RegisterWebhookWithThirdParty' {Maybe Text
webhookName :: Maybe Text
$sel:webhookName:RegisterWebhookWithThirdParty' :: RegisterWebhookWithThirdParty -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"webhookName" 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
webhookName]
      )

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

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

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

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

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

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