{-# 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.CodeCommit.CreatePullRequestApprovalRule
-- 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 approval rule for a pull request.
module Amazonka.CodeCommit.CreatePullRequestApprovalRule
  ( -- * Creating a Request
    CreatePullRequestApprovalRule (..),
    newCreatePullRequestApprovalRule,

    -- * Request Lenses
    createPullRequestApprovalRule_pullRequestId,
    createPullRequestApprovalRule_approvalRuleName,
    createPullRequestApprovalRule_approvalRuleContent,

    -- * Destructuring the Response
    CreatePullRequestApprovalRuleResponse (..),
    newCreatePullRequestApprovalRuleResponse,

    -- * Response Lenses
    createPullRequestApprovalRuleResponse_httpStatus,
    createPullRequestApprovalRuleResponse_approvalRule,
  )
where

import Amazonka.CodeCommit.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:/ 'newCreatePullRequestApprovalRule' smart constructor.
data CreatePullRequestApprovalRule = CreatePullRequestApprovalRule'
  { -- | The system-generated ID of the pull request for which you want to create
    -- the approval rule.
    CreatePullRequestApprovalRule -> Text
pullRequestId :: Prelude.Text,
    -- | The name for the approval rule.
    CreatePullRequestApprovalRule -> Text
approvalRuleName :: Prelude.Text,
    -- | The content of the approval rule, including the number of approvals
    -- needed and the structure of an approval pool defined for approvals, if
    -- any. For more information about approval pools, see the AWS CodeCommit
    -- User Guide.
    --
    -- When you create the content of the approval rule, you can specify
    -- approvers in an approval pool in one of two ways:
    --
    -- -   __CodeCommitApprovers__: This option only requires an AWS account
    --     and a resource. It can be used for both IAM users and federated
    --     access users whose name matches the provided resource name. This is
    --     a very powerful option that offers a great deal of flexibility. For
    --     example, if you specify the AWS account /123456789012/ and
    --     /Mary_Major/, all of the following would be counted as approvals
    --     coming from that user:
    --
    --     -   An IAM user in the account
    --         (arn:aws:iam::/123456789012/:user\//Mary_Major/)
    --
    --     -   A federated user identified in IAM as Mary_Major
    --         (arn:aws:sts::/123456789012/:federated-user\//Mary_Major/)
    --
    --     This option does not recognize an active session of someone assuming
    --     the role of CodeCommitReview with a role session name of
    --     /Mary_Major/
    --     (arn:aws:sts::/123456789012/:assumed-role\/CodeCommitReview\//Mary_Major/)
    --     unless you include a wildcard (*Mary_Major).
    --
    -- -   __Fully qualified ARN__: This option allows you to specify the fully
    --     qualified Amazon Resource Name (ARN) of the IAM user or role.
    --
    -- For more information about IAM ARNs, wildcards, and formats, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_identifiers.html IAM Identifiers>
    -- in the /IAM User Guide/.
    CreatePullRequestApprovalRule -> Text
approvalRuleContent :: Prelude.Text
  }
  deriving (CreatePullRequestApprovalRule
-> CreatePullRequestApprovalRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePullRequestApprovalRule
-> CreatePullRequestApprovalRule -> Bool
$c/= :: CreatePullRequestApprovalRule
-> CreatePullRequestApprovalRule -> Bool
== :: CreatePullRequestApprovalRule
-> CreatePullRequestApprovalRule -> Bool
$c== :: CreatePullRequestApprovalRule
-> CreatePullRequestApprovalRule -> Bool
Prelude.Eq, ReadPrec [CreatePullRequestApprovalRule]
ReadPrec CreatePullRequestApprovalRule
Int -> ReadS CreatePullRequestApprovalRule
ReadS [CreatePullRequestApprovalRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePullRequestApprovalRule]
$creadListPrec :: ReadPrec [CreatePullRequestApprovalRule]
readPrec :: ReadPrec CreatePullRequestApprovalRule
$creadPrec :: ReadPrec CreatePullRequestApprovalRule
readList :: ReadS [CreatePullRequestApprovalRule]
$creadList :: ReadS [CreatePullRequestApprovalRule]
readsPrec :: Int -> ReadS CreatePullRequestApprovalRule
$creadsPrec :: Int -> ReadS CreatePullRequestApprovalRule
Prelude.Read, Int -> CreatePullRequestApprovalRule -> ShowS
[CreatePullRequestApprovalRule] -> ShowS
CreatePullRequestApprovalRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePullRequestApprovalRule] -> ShowS
$cshowList :: [CreatePullRequestApprovalRule] -> ShowS
show :: CreatePullRequestApprovalRule -> String
$cshow :: CreatePullRequestApprovalRule -> String
showsPrec :: Int -> CreatePullRequestApprovalRule -> ShowS
$cshowsPrec :: Int -> CreatePullRequestApprovalRule -> ShowS
Prelude.Show, forall x.
Rep CreatePullRequestApprovalRule x
-> CreatePullRequestApprovalRule
forall x.
CreatePullRequestApprovalRule
-> Rep CreatePullRequestApprovalRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreatePullRequestApprovalRule x
-> CreatePullRequestApprovalRule
$cfrom :: forall x.
CreatePullRequestApprovalRule
-> Rep CreatePullRequestApprovalRule x
Prelude.Generic)

-- |
-- Create a value of 'CreatePullRequestApprovalRule' 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:
--
-- 'pullRequestId', 'createPullRequestApprovalRule_pullRequestId' - The system-generated ID of the pull request for which you want to create
-- the approval rule.
--
-- 'approvalRuleName', 'createPullRequestApprovalRule_approvalRuleName' - The name for the approval rule.
--
-- 'approvalRuleContent', 'createPullRequestApprovalRule_approvalRuleContent' - The content of the approval rule, including the number of approvals
-- needed and the structure of an approval pool defined for approvals, if
-- any. For more information about approval pools, see the AWS CodeCommit
-- User Guide.
--
-- When you create the content of the approval rule, you can specify
-- approvers in an approval pool in one of two ways:
--
-- -   __CodeCommitApprovers__: This option only requires an AWS account
--     and a resource. It can be used for both IAM users and federated
--     access users whose name matches the provided resource name. This is
--     a very powerful option that offers a great deal of flexibility. For
--     example, if you specify the AWS account /123456789012/ and
--     /Mary_Major/, all of the following would be counted as approvals
--     coming from that user:
--
--     -   An IAM user in the account
--         (arn:aws:iam::/123456789012/:user\//Mary_Major/)
--
--     -   A federated user identified in IAM as Mary_Major
--         (arn:aws:sts::/123456789012/:federated-user\//Mary_Major/)
--
--     This option does not recognize an active session of someone assuming
--     the role of CodeCommitReview with a role session name of
--     /Mary_Major/
--     (arn:aws:sts::/123456789012/:assumed-role\/CodeCommitReview\//Mary_Major/)
--     unless you include a wildcard (*Mary_Major).
--
-- -   __Fully qualified ARN__: This option allows you to specify the fully
--     qualified Amazon Resource Name (ARN) of the IAM user or role.
--
-- For more information about IAM ARNs, wildcards, and formats, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_identifiers.html IAM Identifiers>
-- in the /IAM User Guide/.
newCreatePullRequestApprovalRule ::
  -- | 'pullRequestId'
  Prelude.Text ->
  -- | 'approvalRuleName'
  Prelude.Text ->
  -- | 'approvalRuleContent'
  Prelude.Text ->
  CreatePullRequestApprovalRule
newCreatePullRequestApprovalRule :: Text -> Text -> Text -> CreatePullRequestApprovalRule
newCreatePullRequestApprovalRule
  Text
pPullRequestId_
  Text
pApprovalRuleName_
  Text
pApprovalRuleContent_ =
    CreatePullRequestApprovalRule'
      { $sel:pullRequestId:CreatePullRequestApprovalRule' :: Text
pullRequestId =
          Text
pPullRequestId_,
        $sel:approvalRuleName:CreatePullRequestApprovalRule' :: Text
approvalRuleName = Text
pApprovalRuleName_,
        $sel:approvalRuleContent:CreatePullRequestApprovalRule' :: Text
approvalRuleContent = Text
pApprovalRuleContent_
      }

-- | The system-generated ID of the pull request for which you want to create
-- the approval rule.
createPullRequestApprovalRule_pullRequestId :: Lens.Lens' CreatePullRequestApprovalRule Prelude.Text
createPullRequestApprovalRule_pullRequestId :: Lens' CreatePullRequestApprovalRule Text
createPullRequestApprovalRule_pullRequestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullRequestApprovalRule' {Text
pullRequestId :: Text
$sel:pullRequestId:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
pullRequestId} -> Text
pullRequestId) (\s :: CreatePullRequestApprovalRule
s@CreatePullRequestApprovalRule' {} Text
a -> CreatePullRequestApprovalRule
s {$sel:pullRequestId:CreatePullRequestApprovalRule' :: Text
pullRequestId = Text
a} :: CreatePullRequestApprovalRule)

-- | The name for the approval rule.
createPullRequestApprovalRule_approvalRuleName :: Lens.Lens' CreatePullRequestApprovalRule Prelude.Text
createPullRequestApprovalRule_approvalRuleName :: Lens' CreatePullRequestApprovalRule Text
createPullRequestApprovalRule_approvalRuleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullRequestApprovalRule' {Text
approvalRuleName :: Text
$sel:approvalRuleName:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
approvalRuleName} -> Text
approvalRuleName) (\s :: CreatePullRequestApprovalRule
s@CreatePullRequestApprovalRule' {} Text
a -> CreatePullRequestApprovalRule
s {$sel:approvalRuleName:CreatePullRequestApprovalRule' :: Text
approvalRuleName = Text
a} :: CreatePullRequestApprovalRule)

-- | The content of the approval rule, including the number of approvals
-- needed and the structure of an approval pool defined for approvals, if
-- any. For more information about approval pools, see the AWS CodeCommit
-- User Guide.
--
-- When you create the content of the approval rule, you can specify
-- approvers in an approval pool in one of two ways:
--
-- -   __CodeCommitApprovers__: This option only requires an AWS account
--     and a resource. It can be used for both IAM users and federated
--     access users whose name matches the provided resource name. This is
--     a very powerful option that offers a great deal of flexibility. For
--     example, if you specify the AWS account /123456789012/ and
--     /Mary_Major/, all of the following would be counted as approvals
--     coming from that user:
--
--     -   An IAM user in the account
--         (arn:aws:iam::/123456789012/:user\//Mary_Major/)
--
--     -   A federated user identified in IAM as Mary_Major
--         (arn:aws:sts::/123456789012/:federated-user\//Mary_Major/)
--
--     This option does not recognize an active session of someone assuming
--     the role of CodeCommitReview with a role session name of
--     /Mary_Major/
--     (arn:aws:sts::/123456789012/:assumed-role\/CodeCommitReview\//Mary_Major/)
--     unless you include a wildcard (*Mary_Major).
--
-- -   __Fully qualified ARN__: This option allows you to specify the fully
--     qualified Amazon Resource Name (ARN) of the IAM user or role.
--
-- For more information about IAM ARNs, wildcards, and formats, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_identifiers.html IAM Identifiers>
-- in the /IAM User Guide/.
createPullRequestApprovalRule_approvalRuleContent :: Lens.Lens' CreatePullRequestApprovalRule Prelude.Text
createPullRequestApprovalRule_approvalRuleContent :: Lens' CreatePullRequestApprovalRule Text
createPullRequestApprovalRule_approvalRuleContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullRequestApprovalRule' {Text
approvalRuleContent :: Text
$sel:approvalRuleContent:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
approvalRuleContent} -> Text
approvalRuleContent) (\s :: CreatePullRequestApprovalRule
s@CreatePullRequestApprovalRule' {} Text
a -> CreatePullRequestApprovalRule
s {$sel:approvalRuleContent:CreatePullRequestApprovalRule' :: Text
approvalRuleContent = Text
a} :: CreatePullRequestApprovalRule)

instance
  Core.AWSRequest
    CreatePullRequestApprovalRule
  where
  type
    AWSResponse CreatePullRequestApprovalRule =
      CreatePullRequestApprovalRuleResponse
  request :: (Service -> Service)
-> CreatePullRequestApprovalRule
-> Request CreatePullRequestApprovalRule
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 CreatePullRequestApprovalRule
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreatePullRequestApprovalRule)))
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 -> ApprovalRule -> CreatePullRequestApprovalRuleResponse
CreatePullRequestApprovalRuleResponse'
            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
"approvalRule")
      )

instance
  Prelude.Hashable
    CreatePullRequestApprovalRule
  where
  hashWithSalt :: Int -> CreatePullRequestApprovalRule -> Int
hashWithSalt Int
_salt CreatePullRequestApprovalRule' {Text
approvalRuleContent :: Text
approvalRuleName :: Text
pullRequestId :: Text
$sel:approvalRuleContent:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
$sel:approvalRuleName:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
$sel:pullRequestId:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pullRequestId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
approvalRuleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
approvalRuleContent

instance Prelude.NFData CreatePullRequestApprovalRule where
  rnf :: CreatePullRequestApprovalRule -> ()
rnf CreatePullRequestApprovalRule' {Text
approvalRuleContent :: Text
approvalRuleName :: Text
pullRequestId :: Text
$sel:approvalRuleContent:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
$sel:approvalRuleName:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
$sel:pullRequestId:CreatePullRequestApprovalRule' :: CreatePullRequestApprovalRule -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
pullRequestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
approvalRuleName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
approvalRuleContent

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

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

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

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

-- |
-- Create a value of 'CreatePullRequestApprovalRuleResponse' 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', 'createPullRequestApprovalRuleResponse_httpStatus' - The response's http status code.
--
-- 'approvalRule', 'createPullRequestApprovalRuleResponse_approvalRule' - Information about the created approval rule.
newCreatePullRequestApprovalRuleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'approvalRule'
  ApprovalRule ->
  CreatePullRequestApprovalRuleResponse
newCreatePullRequestApprovalRuleResponse :: Int -> ApprovalRule -> CreatePullRequestApprovalRuleResponse
newCreatePullRequestApprovalRuleResponse
  Int
pHttpStatus_
  ApprovalRule
pApprovalRule_ =
    CreatePullRequestApprovalRuleResponse'
      { $sel:httpStatus:CreatePullRequestApprovalRuleResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:approvalRule:CreatePullRequestApprovalRuleResponse' :: ApprovalRule
approvalRule = ApprovalRule
pApprovalRule_
      }

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

-- | Information about the created approval rule.
createPullRequestApprovalRuleResponse_approvalRule :: Lens.Lens' CreatePullRequestApprovalRuleResponse ApprovalRule
createPullRequestApprovalRuleResponse_approvalRule :: Lens' CreatePullRequestApprovalRuleResponse ApprovalRule
createPullRequestApprovalRuleResponse_approvalRule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullRequestApprovalRuleResponse' {ApprovalRule
approvalRule :: ApprovalRule
$sel:approvalRule:CreatePullRequestApprovalRuleResponse' :: CreatePullRequestApprovalRuleResponse -> ApprovalRule
approvalRule} -> ApprovalRule
approvalRule) (\s :: CreatePullRequestApprovalRuleResponse
s@CreatePullRequestApprovalRuleResponse' {} ApprovalRule
a -> CreatePullRequestApprovalRuleResponse
s {$sel:approvalRule:CreatePullRequestApprovalRuleResponse' :: ApprovalRule
approvalRule = ApprovalRule
a} :: CreatePullRequestApprovalRuleResponse)

instance
  Prelude.NFData
    CreatePullRequestApprovalRuleResponse
  where
  rnf :: CreatePullRequestApprovalRuleResponse -> ()
rnf CreatePullRequestApprovalRuleResponse' {Int
ApprovalRule
approvalRule :: ApprovalRule
httpStatus :: Int
$sel:approvalRule:CreatePullRequestApprovalRuleResponse' :: CreatePullRequestApprovalRuleResponse -> ApprovalRule
$sel:httpStatus:CreatePullRequestApprovalRuleResponse' :: CreatePullRequestApprovalRuleResponse -> 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 ApprovalRule
approvalRule