{-# 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.OverridePullRequestApprovalRules
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sets aside (overrides) all approval rule requirements for a specified
-- pull request.
module Amazonka.CodeCommit.OverridePullRequestApprovalRules
  ( -- * Creating a Request
    OverridePullRequestApprovalRules (..),
    newOverridePullRequestApprovalRules,

    -- * Request Lenses
    overridePullRequestApprovalRules_pullRequestId,
    overridePullRequestApprovalRules_revisionId,
    overridePullRequestApprovalRules_overrideStatus,

    -- * Destructuring the Response
    OverridePullRequestApprovalRulesResponse (..),
    newOverridePullRequestApprovalRulesResponse,
  )
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:/ 'newOverridePullRequestApprovalRules' smart constructor.
data OverridePullRequestApprovalRules = OverridePullRequestApprovalRules'
  { -- | The system-generated ID of the pull request for which you want to
    -- override all approval rule requirements. To get this information, use
    -- GetPullRequest.
    OverridePullRequestApprovalRules -> Text
pullRequestId :: Prelude.Text,
    -- | The system-generated ID of the most recent revision of the pull request.
    -- You cannot override approval rules for anything but the most recent
    -- revision of a pull request. To get the revision ID, use GetPullRequest.
    OverridePullRequestApprovalRules -> Text
revisionId :: Prelude.Text,
    -- | Whether you want to set aside approval rule requirements for the pull
    -- request (OVERRIDE) or revoke a previous override and apply approval rule
    -- requirements (REVOKE). REVOKE status is not stored.
    OverridePullRequestApprovalRules -> OverrideStatus
overrideStatus :: OverrideStatus
  }
  deriving (OverridePullRequestApprovalRules
-> OverridePullRequestApprovalRules -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverridePullRequestApprovalRules
-> OverridePullRequestApprovalRules -> Bool
$c/= :: OverridePullRequestApprovalRules
-> OverridePullRequestApprovalRules -> Bool
== :: OverridePullRequestApprovalRules
-> OverridePullRequestApprovalRules -> Bool
$c== :: OverridePullRequestApprovalRules
-> OverridePullRequestApprovalRules -> Bool
Prelude.Eq, ReadPrec [OverridePullRequestApprovalRules]
ReadPrec OverridePullRequestApprovalRules
Int -> ReadS OverridePullRequestApprovalRules
ReadS [OverridePullRequestApprovalRules]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OverridePullRequestApprovalRules]
$creadListPrec :: ReadPrec [OverridePullRequestApprovalRules]
readPrec :: ReadPrec OverridePullRequestApprovalRules
$creadPrec :: ReadPrec OverridePullRequestApprovalRules
readList :: ReadS [OverridePullRequestApprovalRules]
$creadList :: ReadS [OverridePullRequestApprovalRules]
readsPrec :: Int -> ReadS OverridePullRequestApprovalRules
$creadsPrec :: Int -> ReadS OverridePullRequestApprovalRules
Prelude.Read, Int -> OverridePullRequestApprovalRules -> ShowS
[OverridePullRequestApprovalRules] -> ShowS
OverridePullRequestApprovalRules -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OverridePullRequestApprovalRules] -> ShowS
$cshowList :: [OverridePullRequestApprovalRules] -> ShowS
show :: OverridePullRequestApprovalRules -> String
$cshow :: OverridePullRequestApprovalRules -> String
showsPrec :: Int -> OverridePullRequestApprovalRules -> ShowS
$cshowsPrec :: Int -> OverridePullRequestApprovalRules -> ShowS
Prelude.Show, forall x.
Rep OverridePullRequestApprovalRules x
-> OverridePullRequestApprovalRules
forall x.
OverridePullRequestApprovalRules
-> Rep OverridePullRequestApprovalRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep OverridePullRequestApprovalRules x
-> OverridePullRequestApprovalRules
$cfrom :: forall x.
OverridePullRequestApprovalRules
-> Rep OverridePullRequestApprovalRules x
Prelude.Generic)

-- |
-- Create a value of 'OverridePullRequestApprovalRules' 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', 'overridePullRequestApprovalRules_pullRequestId' - The system-generated ID of the pull request for which you want to
-- override all approval rule requirements. To get this information, use
-- GetPullRequest.
--
-- 'revisionId', 'overridePullRequestApprovalRules_revisionId' - The system-generated ID of the most recent revision of the pull request.
-- You cannot override approval rules for anything but the most recent
-- revision of a pull request. To get the revision ID, use GetPullRequest.
--
-- 'overrideStatus', 'overridePullRequestApprovalRules_overrideStatus' - Whether you want to set aside approval rule requirements for the pull
-- request (OVERRIDE) or revoke a previous override and apply approval rule
-- requirements (REVOKE). REVOKE status is not stored.
newOverridePullRequestApprovalRules ::
  -- | 'pullRequestId'
  Prelude.Text ->
  -- | 'revisionId'
  Prelude.Text ->
  -- | 'overrideStatus'
  OverrideStatus ->
  OverridePullRequestApprovalRules
newOverridePullRequestApprovalRules :: Text -> Text -> OverrideStatus -> OverridePullRequestApprovalRules
newOverridePullRequestApprovalRules
  Text
pPullRequestId_
  Text
pRevisionId_
  OverrideStatus
pOverrideStatus_ =
    OverridePullRequestApprovalRules'
      { $sel:pullRequestId:OverridePullRequestApprovalRules' :: Text
pullRequestId =
          Text
pPullRequestId_,
        $sel:revisionId:OverridePullRequestApprovalRules' :: Text
revisionId = Text
pRevisionId_,
        $sel:overrideStatus:OverridePullRequestApprovalRules' :: OverrideStatus
overrideStatus = OverrideStatus
pOverrideStatus_
      }

-- | The system-generated ID of the pull request for which you want to
-- override all approval rule requirements. To get this information, use
-- GetPullRequest.
overridePullRequestApprovalRules_pullRequestId :: Lens.Lens' OverridePullRequestApprovalRules Prelude.Text
overridePullRequestApprovalRules_pullRequestId :: Lens' OverridePullRequestApprovalRules Text
overridePullRequestApprovalRules_pullRequestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OverridePullRequestApprovalRules' {Text
pullRequestId :: Text
$sel:pullRequestId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> Text
pullRequestId} -> Text
pullRequestId) (\s :: OverridePullRequestApprovalRules
s@OverridePullRequestApprovalRules' {} Text
a -> OverridePullRequestApprovalRules
s {$sel:pullRequestId:OverridePullRequestApprovalRules' :: Text
pullRequestId = Text
a} :: OverridePullRequestApprovalRules)

-- | The system-generated ID of the most recent revision of the pull request.
-- You cannot override approval rules for anything but the most recent
-- revision of a pull request. To get the revision ID, use GetPullRequest.
overridePullRequestApprovalRules_revisionId :: Lens.Lens' OverridePullRequestApprovalRules Prelude.Text
overridePullRequestApprovalRules_revisionId :: Lens' OverridePullRequestApprovalRules Text
overridePullRequestApprovalRules_revisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OverridePullRequestApprovalRules' {Text
revisionId :: Text
$sel:revisionId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> Text
revisionId} -> Text
revisionId) (\s :: OverridePullRequestApprovalRules
s@OverridePullRequestApprovalRules' {} Text
a -> OverridePullRequestApprovalRules
s {$sel:revisionId:OverridePullRequestApprovalRules' :: Text
revisionId = Text
a} :: OverridePullRequestApprovalRules)

-- | Whether you want to set aside approval rule requirements for the pull
-- request (OVERRIDE) or revoke a previous override and apply approval rule
-- requirements (REVOKE). REVOKE status is not stored.
overridePullRequestApprovalRules_overrideStatus :: Lens.Lens' OverridePullRequestApprovalRules OverrideStatus
overridePullRequestApprovalRules_overrideStatus :: Lens' OverridePullRequestApprovalRules OverrideStatus
overridePullRequestApprovalRules_overrideStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OverridePullRequestApprovalRules' {OverrideStatus
overrideStatus :: OverrideStatus
$sel:overrideStatus:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> OverrideStatus
overrideStatus} -> OverrideStatus
overrideStatus) (\s :: OverridePullRequestApprovalRules
s@OverridePullRequestApprovalRules' {} OverrideStatus
a -> OverridePullRequestApprovalRules
s {$sel:overrideStatus:OverridePullRequestApprovalRules' :: OverrideStatus
overrideStatus = OverrideStatus
a} :: OverridePullRequestApprovalRules)

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

instance
  Prelude.Hashable
    OverridePullRequestApprovalRules
  where
  hashWithSalt :: Int -> OverridePullRequestApprovalRules -> Int
hashWithSalt
    Int
_salt
    OverridePullRequestApprovalRules' {Text
OverrideStatus
overrideStatus :: OverrideStatus
revisionId :: Text
pullRequestId :: Text
$sel:overrideStatus:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> OverrideStatus
$sel:revisionId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> Text
$sel:pullRequestId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pullRequestId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
revisionId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` OverrideStatus
overrideStatus

instance
  Prelude.NFData
    OverridePullRequestApprovalRules
  where
  rnf :: OverridePullRequestApprovalRules -> ()
rnf OverridePullRequestApprovalRules' {Text
OverrideStatus
overrideStatus :: OverrideStatus
revisionId :: Text
pullRequestId :: Text
$sel:overrideStatus:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> OverrideStatus
$sel:revisionId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> Text
$sel:pullRequestId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> 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
revisionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf OverrideStatus
overrideStatus

instance
  Data.ToHeaders
    OverridePullRequestApprovalRules
  where
  toHeaders :: OverridePullRequestApprovalRules -> [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
"CodeCommit_20150413.OverridePullRequestApprovalRules" ::
                          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 OverridePullRequestApprovalRules where
  toJSON :: OverridePullRequestApprovalRules -> Value
toJSON OverridePullRequestApprovalRules' {Text
OverrideStatus
overrideStatus :: OverrideStatus
revisionId :: Text
pullRequestId :: Text
$sel:overrideStatus:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> OverrideStatus
$sel:revisionId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> Text
$sel:pullRequestId:OverridePullRequestApprovalRules' :: OverridePullRequestApprovalRules -> 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
"revisionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
revisionId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"overrideStatus" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= OverrideStatus
overrideStatus)
          ]
      )

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

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

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

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

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