{-# 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.Amplify.CreateWebhook
-- 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 new webhook on an Amplify app.
module Amazonka.Amplify.CreateWebhook
  ( -- * Creating a Request
    CreateWebhook (..),
    newCreateWebhook,

    -- * Request Lenses
    createWebhook_description,
    createWebhook_appId,
    createWebhook_branchName,

    -- * Destructuring the Response
    CreateWebhookResponse (..),
    newCreateWebhookResponse,

    -- * Response Lenses
    createWebhookResponse_httpStatus,
    createWebhookResponse_webhook,
  )
where

import Amazonka.Amplify.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

-- | The request structure for the create webhook request.
--
-- /See:/ 'newCreateWebhook' smart constructor.
data CreateWebhook = CreateWebhook'
  { -- | The description for a webhook.
    CreateWebhook -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The unique ID for an Amplify app.
    CreateWebhook -> Text
appId :: Prelude.Text,
    -- | The name for a branch that is part of an Amplify app.
    CreateWebhook -> Text
branchName :: Prelude.Text
  }
  deriving (CreateWebhook -> CreateWebhook -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWebhook -> CreateWebhook -> Bool
$c/= :: CreateWebhook -> CreateWebhook -> Bool
== :: CreateWebhook -> CreateWebhook -> Bool
$c== :: CreateWebhook -> CreateWebhook -> Bool
Prelude.Eq, ReadPrec [CreateWebhook]
ReadPrec CreateWebhook
Int -> ReadS CreateWebhook
ReadS [CreateWebhook]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWebhook]
$creadListPrec :: ReadPrec [CreateWebhook]
readPrec :: ReadPrec CreateWebhook
$creadPrec :: ReadPrec CreateWebhook
readList :: ReadS [CreateWebhook]
$creadList :: ReadS [CreateWebhook]
readsPrec :: Int -> ReadS CreateWebhook
$creadsPrec :: Int -> ReadS CreateWebhook
Prelude.Read, Int -> CreateWebhook -> ShowS
[CreateWebhook] -> ShowS
CreateWebhook -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWebhook] -> ShowS
$cshowList :: [CreateWebhook] -> ShowS
show :: CreateWebhook -> String
$cshow :: CreateWebhook -> String
showsPrec :: Int -> CreateWebhook -> ShowS
$cshowsPrec :: Int -> CreateWebhook -> ShowS
Prelude.Show, forall x. Rep CreateWebhook x -> CreateWebhook
forall x. CreateWebhook -> Rep CreateWebhook x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWebhook x -> CreateWebhook
$cfrom :: forall x. CreateWebhook -> Rep CreateWebhook x
Prelude.Generic)

-- |
-- Create a value of 'CreateWebhook' 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:
--
-- 'description', 'createWebhook_description' - The description for a webhook.
--
-- 'appId', 'createWebhook_appId' - The unique ID for an Amplify app.
--
-- 'branchName', 'createWebhook_branchName' - The name for a branch that is part of an Amplify app.
newCreateWebhook ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'branchName'
  Prelude.Text ->
  CreateWebhook
newCreateWebhook :: Text -> Text -> CreateWebhook
newCreateWebhook Text
pAppId_ Text
pBranchName_ =
  CreateWebhook'
    { $sel:description:CreateWebhook' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:appId:CreateWebhook' :: Text
appId = Text
pAppId_,
      $sel:branchName:CreateWebhook' :: Text
branchName = Text
pBranchName_
    }

-- | The description for a webhook.
createWebhook_description :: Lens.Lens' CreateWebhook (Prelude.Maybe Prelude.Text)
createWebhook_description :: Lens' CreateWebhook (Maybe Text)
createWebhook_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWebhook' {Maybe Text
description :: Maybe Text
$sel:description:CreateWebhook' :: CreateWebhook -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateWebhook
s@CreateWebhook' {} Maybe Text
a -> CreateWebhook
s {$sel:description:CreateWebhook' :: Maybe Text
description = Maybe Text
a} :: CreateWebhook)

-- | The unique ID for an Amplify app.
createWebhook_appId :: Lens.Lens' CreateWebhook Prelude.Text
createWebhook_appId :: Lens' CreateWebhook Text
createWebhook_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWebhook' {Text
appId :: Text
$sel:appId:CreateWebhook' :: CreateWebhook -> Text
appId} -> Text
appId) (\s :: CreateWebhook
s@CreateWebhook' {} Text
a -> CreateWebhook
s {$sel:appId:CreateWebhook' :: Text
appId = Text
a} :: CreateWebhook)

-- | The name for a branch that is part of an Amplify app.
createWebhook_branchName :: Lens.Lens' CreateWebhook Prelude.Text
createWebhook_branchName :: Lens' CreateWebhook Text
createWebhook_branchName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWebhook' {Text
branchName :: Text
$sel:branchName:CreateWebhook' :: CreateWebhook -> Text
branchName} -> Text
branchName) (\s :: CreateWebhook
s@CreateWebhook' {} Text
a -> CreateWebhook
s {$sel:branchName:CreateWebhook' :: Text
branchName = Text
a} :: CreateWebhook)

instance Core.AWSRequest CreateWebhook where
  type
    AWSResponse CreateWebhook =
      CreateWebhookResponse
  request :: (Service -> Service) -> CreateWebhook -> Request CreateWebhook
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 CreateWebhook
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateWebhook)))
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 ->
          Int -> Webhook -> CreateWebhookResponse
CreateWebhookResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"webhook")
      )

instance Prelude.Hashable CreateWebhook where
  hashWithSalt :: Int -> CreateWebhook -> Int
hashWithSalt Int
_salt CreateWebhook' {Maybe Text
Text
branchName :: Text
appId :: Text
description :: Maybe Text
$sel:branchName:CreateWebhook' :: CreateWebhook -> Text
$sel:appId:CreateWebhook' :: CreateWebhook -> Text
$sel:description:CreateWebhook' :: CreateWebhook -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
branchName

instance Prelude.NFData CreateWebhook where
  rnf :: CreateWebhook -> ()
rnf CreateWebhook' {Maybe Text
Text
branchName :: Text
appId :: Text
description :: Maybe Text
$sel:branchName:CreateWebhook' :: CreateWebhook -> Text
$sel:appId:CreateWebhook' :: CreateWebhook -> Text
$sel:description:CreateWebhook' :: CreateWebhook -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
branchName

instance Data.ToHeaders CreateWebhook where
  toHeaders :: CreateWebhook -> 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 CreateWebhook where
  toJSON :: CreateWebhook -> Value
toJSON CreateWebhook' {Maybe Text
Text
branchName :: Text
appId :: Text
description :: Maybe Text
$sel:branchName:CreateWebhook' :: CreateWebhook -> Text
$sel:appId:CreateWebhook' :: CreateWebhook -> Text
$sel:description:CreateWebhook' :: CreateWebhook -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            forall a. a -> Maybe a
Prelude.Just (Key
"branchName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
branchName)
          ]
      )

instance Data.ToPath CreateWebhook where
  toPath :: CreateWebhook -> ByteString
toPath CreateWebhook' {Maybe Text
Text
branchName :: Text
appId :: Text
description :: Maybe Text
$sel:branchName:CreateWebhook' :: CreateWebhook -> Text
$sel:appId:CreateWebhook' :: CreateWebhook -> Text
$sel:description:CreateWebhook' :: CreateWebhook -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/apps/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId, ByteString
"/webhooks"]

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

-- | The result structure for the create webhook request.
--
-- /See:/ 'newCreateWebhookResponse' smart constructor.
data CreateWebhookResponse = CreateWebhookResponse'
  { -- | The response's http status code.
    CreateWebhookResponse -> Int
httpStatus :: Prelude.Int,
    -- | Describes a webhook that connects repository events to an Amplify app.
    CreateWebhookResponse -> Webhook
webhook :: Webhook
  }
  deriving (CreateWebhookResponse -> CreateWebhookResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWebhookResponse -> CreateWebhookResponse -> Bool
$c/= :: CreateWebhookResponse -> CreateWebhookResponse -> Bool
== :: CreateWebhookResponse -> CreateWebhookResponse -> Bool
$c== :: CreateWebhookResponse -> CreateWebhookResponse -> Bool
Prelude.Eq, ReadPrec [CreateWebhookResponse]
ReadPrec CreateWebhookResponse
Int -> ReadS CreateWebhookResponse
ReadS [CreateWebhookResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWebhookResponse]
$creadListPrec :: ReadPrec [CreateWebhookResponse]
readPrec :: ReadPrec CreateWebhookResponse
$creadPrec :: ReadPrec CreateWebhookResponse
readList :: ReadS [CreateWebhookResponse]
$creadList :: ReadS [CreateWebhookResponse]
readsPrec :: Int -> ReadS CreateWebhookResponse
$creadsPrec :: Int -> ReadS CreateWebhookResponse
Prelude.Read, Int -> CreateWebhookResponse -> ShowS
[CreateWebhookResponse] -> ShowS
CreateWebhookResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWebhookResponse] -> ShowS
$cshowList :: [CreateWebhookResponse] -> ShowS
show :: CreateWebhookResponse -> String
$cshow :: CreateWebhookResponse -> String
showsPrec :: Int -> CreateWebhookResponse -> ShowS
$cshowsPrec :: Int -> CreateWebhookResponse -> ShowS
Prelude.Show, forall x. Rep CreateWebhookResponse x -> CreateWebhookResponse
forall x. CreateWebhookResponse -> Rep CreateWebhookResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWebhookResponse x -> CreateWebhookResponse
$cfrom :: forall x. CreateWebhookResponse -> Rep CreateWebhookResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateWebhookResponse' 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', 'createWebhookResponse_httpStatus' - The response's http status code.
--
-- 'webhook', 'createWebhookResponse_webhook' - Describes a webhook that connects repository events to an Amplify app.
newCreateWebhookResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'webhook'
  Webhook ->
  CreateWebhookResponse
newCreateWebhookResponse :: Int -> Webhook -> CreateWebhookResponse
newCreateWebhookResponse Int
pHttpStatus_ Webhook
pWebhook_ =
  CreateWebhookResponse'
    { $sel:httpStatus:CreateWebhookResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:webhook:CreateWebhookResponse' :: Webhook
webhook = Webhook
pWebhook_
    }

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

-- | Describes a webhook that connects repository events to an Amplify app.
createWebhookResponse_webhook :: Lens.Lens' CreateWebhookResponse Webhook
createWebhookResponse_webhook :: Lens' CreateWebhookResponse Webhook
createWebhookResponse_webhook = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWebhookResponse' {Webhook
webhook :: Webhook
$sel:webhook:CreateWebhookResponse' :: CreateWebhookResponse -> Webhook
webhook} -> Webhook
webhook) (\s :: CreateWebhookResponse
s@CreateWebhookResponse' {} Webhook
a -> CreateWebhookResponse
s {$sel:webhook:CreateWebhookResponse' :: Webhook
webhook = Webhook
a} :: CreateWebhookResponse)

instance Prelude.NFData CreateWebhookResponse where
  rnf :: CreateWebhookResponse -> ()
rnf CreateWebhookResponse' {Int
Webhook
webhook :: Webhook
httpStatus :: Int
$sel:webhook:CreateWebhookResponse' :: CreateWebhookResponse -> Webhook
$sel:httpStatus:CreateWebhookResponse' :: CreateWebhookResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Webhook
webhook