{-# 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.MergeBranchesBySquash
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Merges two branches using the squash merge strategy.
module Amazonka.CodeCommit.MergeBranchesBySquash
  ( -- * Creating a Request
    MergeBranchesBySquash (..),
    newMergeBranchesBySquash,

    -- * Request Lenses
    mergeBranchesBySquash_authorName,
    mergeBranchesBySquash_commitMessage,
    mergeBranchesBySquash_conflictDetailLevel,
    mergeBranchesBySquash_conflictResolution,
    mergeBranchesBySquash_conflictResolutionStrategy,
    mergeBranchesBySquash_email,
    mergeBranchesBySquash_keepEmptyFolders,
    mergeBranchesBySquash_targetBranch,
    mergeBranchesBySquash_repositoryName,
    mergeBranchesBySquash_sourceCommitSpecifier,
    mergeBranchesBySquash_destinationCommitSpecifier,

    -- * Destructuring the Response
    MergeBranchesBySquashResponse (..),
    newMergeBranchesBySquashResponse,

    -- * Response Lenses
    mergeBranchesBySquashResponse_commitId,
    mergeBranchesBySquashResponse_treeId,
    mergeBranchesBySquashResponse_httpStatus,
  )
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:/ 'newMergeBranchesBySquash' smart constructor.
data MergeBranchesBySquash = MergeBranchesBySquash'
  { -- | The name of the author who created the commit. This information is used
    -- as both the author and committer for the commit.
    MergeBranchesBySquash -> Maybe Text
authorName :: Prelude.Maybe Prelude.Text,
    -- | The commit message for the merge.
    MergeBranchesBySquash -> Maybe Text
commitMessage :: Prelude.Maybe Prelude.Text,
    -- | The level of conflict detail to use. If unspecified, the default
    -- FILE_LEVEL is used, which returns a not-mergeable result if the same
    -- file has differences in both branches. If LINE_LEVEL is specified, a
    -- conflict is considered not mergeable if the same file in both branches
    -- has differences on the same line.
    MergeBranchesBySquash -> Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel :: Prelude.Maybe ConflictDetailLevelTypeEnum,
    -- | If AUTOMERGE is the conflict resolution strategy, a list of inputs to
    -- use when resolving conflicts during a merge.
    MergeBranchesBySquash -> Maybe ConflictResolution
conflictResolution :: Prelude.Maybe ConflictResolution,
    -- | Specifies which branch to use when resolving conflicts, or whether to
    -- attempt automatically merging two versions of a file. The default is
    -- NONE, which requires any conflicts to be resolved manually before the
    -- merge operation is successful.
    MergeBranchesBySquash -> Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy :: Prelude.Maybe ConflictResolutionStrategyTypeEnum,
    -- | The email address of the person merging the branches. This information
    -- is used in the commit information for the merge.
    MergeBranchesBySquash -> Maybe Text
email :: Prelude.Maybe Prelude.Text,
    -- | If the commit contains deletions, whether to keep a folder or folder
    -- structure if the changes leave the folders empty. If this is specified
    -- as true, a .gitkeep file is created for empty folders. The default is
    -- false.
    MergeBranchesBySquash -> Maybe Bool
keepEmptyFolders :: Prelude.Maybe Prelude.Bool,
    -- | The branch where the merge is applied.
    MergeBranchesBySquash -> Maybe Text
targetBranch :: Prelude.Maybe Prelude.Text,
    -- | The name of the repository where you want to merge two branches.
    MergeBranchesBySquash -> Text
repositoryName :: Prelude.Text,
    -- | The branch, tag, HEAD, or other fully qualified reference used to
    -- identify a commit (for example, a branch name or a full commit ID).
    MergeBranchesBySquash -> Text
sourceCommitSpecifier :: Prelude.Text,
    -- | The branch, tag, HEAD, or other fully qualified reference used to
    -- identify a commit (for example, a branch name or a full commit ID).
    MergeBranchesBySquash -> Text
destinationCommitSpecifier :: Prelude.Text
  }
  deriving (MergeBranchesBySquash -> MergeBranchesBySquash -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MergeBranchesBySquash -> MergeBranchesBySquash -> Bool
$c/= :: MergeBranchesBySquash -> MergeBranchesBySquash -> Bool
== :: MergeBranchesBySquash -> MergeBranchesBySquash -> Bool
$c== :: MergeBranchesBySquash -> MergeBranchesBySquash -> Bool
Prelude.Eq, ReadPrec [MergeBranchesBySquash]
ReadPrec MergeBranchesBySquash
Int -> ReadS MergeBranchesBySquash
ReadS [MergeBranchesBySquash]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MergeBranchesBySquash]
$creadListPrec :: ReadPrec [MergeBranchesBySquash]
readPrec :: ReadPrec MergeBranchesBySquash
$creadPrec :: ReadPrec MergeBranchesBySquash
readList :: ReadS [MergeBranchesBySquash]
$creadList :: ReadS [MergeBranchesBySquash]
readsPrec :: Int -> ReadS MergeBranchesBySquash
$creadsPrec :: Int -> ReadS MergeBranchesBySquash
Prelude.Read, Int -> MergeBranchesBySquash -> ShowS
[MergeBranchesBySquash] -> ShowS
MergeBranchesBySquash -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MergeBranchesBySquash] -> ShowS
$cshowList :: [MergeBranchesBySquash] -> ShowS
show :: MergeBranchesBySquash -> String
$cshow :: MergeBranchesBySquash -> String
showsPrec :: Int -> MergeBranchesBySquash -> ShowS
$cshowsPrec :: Int -> MergeBranchesBySquash -> ShowS
Prelude.Show, forall x. Rep MergeBranchesBySquash x -> MergeBranchesBySquash
forall x. MergeBranchesBySquash -> Rep MergeBranchesBySquash x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MergeBranchesBySquash x -> MergeBranchesBySquash
$cfrom :: forall x. MergeBranchesBySquash -> Rep MergeBranchesBySquash x
Prelude.Generic)

-- |
-- Create a value of 'MergeBranchesBySquash' 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:
--
-- 'authorName', 'mergeBranchesBySquash_authorName' - The name of the author who created the commit. This information is used
-- as both the author and committer for the commit.
--
-- 'commitMessage', 'mergeBranchesBySquash_commitMessage' - The commit message for the merge.
--
-- 'conflictDetailLevel', 'mergeBranchesBySquash_conflictDetailLevel' - The level of conflict detail to use. If unspecified, the default
-- FILE_LEVEL is used, which returns a not-mergeable result if the same
-- file has differences in both branches. If LINE_LEVEL is specified, a
-- conflict is considered not mergeable if the same file in both branches
-- has differences on the same line.
--
-- 'conflictResolution', 'mergeBranchesBySquash_conflictResolution' - If AUTOMERGE is the conflict resolution strategy, a list of inputs to
-- use when resolving conflicts during a merge.
--
-- 'conflictResolutionStrategy', 'mergeBranchesBySquash_conflictResolutionStrategy' - Specifies which branch to use when resolving conflicts, or whether to
-- attempt automatically merging two versions of a file. The default is
-- NONE, which requires any conflicts to be resolved manually before the
-- merge operation is successful.
--
-- 'email', 'mergeBranchesBySquash_email' - The email address of the person merging the branches. This information
-- is used in the commit information for the merge.
--
-- 'keepEmptyFolders', 'mergeBranchesBySquash_keepEmptyFolders' - If the commit contains deletions, whether to keep a folder or folder
-- structure if the changes leave the folders empty. If this is specified
-- as true, a .gitkeep file is created for empty folders. The default is
-- false.
--
-- 'targetBranch', 'mergeBranchesBySquash_targetBranch' - The branch where the merge is applied.
--
-- 'repositoryName', 'mergeBranchesBySquash_repositoryName' - The name of the repository where you want to merge two branches.
--
-- 'sourceCommitSpecifier', 'mergeBranchesBySquash_sourceCommitSpecifier' - The branch, tag, HEAD, or other fully qualified reference used to
-- identify a commit (for example, a branch name or a full commit ID).
--
-- 'destinationCommitSpecifier', 'mergeBranchesBySquash_destinationCommitSpecifier' - The branch, tag, HEAD, or other fully qualified reference used to
-- identify a commit (for example, a branch name or a full commit ID).
newMergeBranchesBySquash ::
  -- | 'repositoryName'
  Prelude.Text ->
  -- | 'sourceCommitSpecifier'
  Prelude.Text ->
  -- | 'destinationCommitSpecifier'
  Prelude.Text ->
  MergeBranchesBySquash
newMergeBranchesBySquash :: Text -> Text -> Text -> MergeBranchesBySquash
newMergeBranchesBySquash
  Text
pRepositoryName_
  Text
pSourceCommitSpecifier_
  Text
pDestinationCommitSpecifier_ =
    MergeBranchesBySquash'
      { $sel:authorName:MergeBranchesBySquash' :: Maybe Text
authorName =
          forall a. Maybe a
Prelude.Nothing,
        $sel:commitMessage:MergeBranchesBySquash' :: Maybe Text
commitMessage = forall a. Maybe a
Prelude.Nothing,
        $sel:conflictDetailLevel:MergeBranchesBySquash' :: Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel = forall a. Maybe a
Prelude.Nothing,
        $sel:conflictResolution:MergeBranchesBySquash' :: Maybe ConflictResolution
conflictResolution = forall a. Maybe a
Prelude.Nothing,
        $sel:conflictResolutionStrategy:MergeBranchesBySquash' :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy = forall a. Maybe a
Prelude.Nothing,
        $sel:email:MergeBranchesBySquash' :: Maybe Text
email = forall a. Maybe a
Prelude.Nothing,
        $sel:keepEmptyFolders:MergeBranchesBySquash' :: Maybe Bool
keepEmptyFolders = forall a. Maybe a
Prelude.Nothing,
        $sel:targetBranch:MergeBranchesBySquash' :: Maybe Text
targetBranch = forall a. Maybe a
Prelude.Nothing,
        $sel:repositoryName:MergeBranchesBySquash' :: Text
repositoryName = Text
pRepositoryName_,
        $sel:sourceCommitSpecifier:MergeBranchesBySquash' :: Text
sourceCommitSpecifier = Text
pSourceCommitSpecifier_,
        $sel:destinationCommitSpecifier:MergeBranchesBySquash' :: Text
destinationCommitSpecifier =
          Text
pDestinationCommitSpecifier_
      }

-- | The name of the author who created the commit. This information is used
-- as both the author and committer for the commit.
mergeBranchesBySquash_authorName :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe Prelude.Text)
mergeBranchesBySquash_authorName :: Lens' MergeBranchesBySquash (Maybe Text)
mergeBranchesBySquash_authorName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe Text
authorName :: Maybe Text
$sel:authorName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
authorName} -> Maybe Text
authorName) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe Text
a -> MergeBranchesBySquash
s {$sel:authorName:MergeBranchesBySquash' :: Maybe Text
authorName = Maybe Text
a} :: MergeBranchesBySquash)

-- | The commit message for the merge.
mergeBranchesBySquash_commitMessage :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe Prelude.Text)
mergeBranchesBySquash_commitMessage :: Lens' MergeBranchesBySquash (Maybe Text)
mergeBranchesBySquash_commitMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe Text
commitMessage :: Maybe Text
$sel:commitMessage:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
commitMessage} -> Maybe Text
commitMessage) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe Text
a -> MergeBranchesBySquash
s {$sel:commitMessage:MergeBranchesBySquash' :: Maybe Text
commitMessage = Maybe Text
a} :: MergeBranchesBySquash)

-- | The level of conflict detail to use. If unspecified, the default
-- FILE_LEVEL is used, which returns a not-mergeable result if the same
-- file has differences in both branches. If LINE_LEVEL is specified, a
-- conflict is considered not mergeable if the same file in both branches
-- has differences on the same line.
mergeBranchesBySquash_conflictDetailLevel :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe ConflictDetailLevelTypeEnum)
mergeBranchesBySquash_conflictDetailLevel :: Lens' MergeBranchesBySquash (Maybe ConflictDetailLevelTypeEnum)
mergeBranchesBySquash_conflictDetailLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:conflictDetailLevel:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel} -> Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe ConflictDetailLevelTypeEnum
a -> MergeBranchesBySquash
s {$sel:conflictDetailLevel:MergeBranchesBySquash' :: Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel = Maybe ConflictDetailLevelTypeEnum
a} :: MergeBranchesBySquash)

-- | If AUTOMERGE is the conflict resolution strategy, a list of inputs to
-- use when resolving conflicts during a merge.
mergeBranchesBySquash_conflictResolution :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe ConflictResolution)
mergeBranchesBySquash_conflictResolution :: Lens' MergeBranchesBySquash (Maybe ConflictResolution)
mergeBranchesBySquash_conflictResolution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe ConflictResolution
conflictResolution :: Maybe ConflictResolution
$sel:conflictResolution:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolution
conflictResolution} -> Maybe ConflictResolution
conflictResolution) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe ConflictResolution
a -> MergeBranchesBySquash
s {$sel:conflictResolution:MergeBranchesBySquash' :: Maybe ConflictResolution
conflictResolution = Maybe ConflictResolution
a} :: MergeBranchesBySquash)

-- | Specifies which branch to use when resolving conflicts, or whether to
-- attempt automatically merging two versions of a file. The default is
-- NONE, which requires any conflicts to be resolved manually before the
-- merge operation is successful.
mergeBranchesBySquash_conflictResolutionStrategy :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe ConflictResolutionStrategyTypeEnum)
mergeBranchesBySquash_conflictResolutionStrategy :: Lens'
  MergeBranchesBySquash (Maybe ConflictResolutionStrategyTypeEnum)
mergeBranchesBySquash_conflictResolutionStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictResolutionStrategy:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy} -> Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe ConflictResolutionStrategyTypeEnum
a -> MergeBranchesBySquash
s {$sel:conflictResolutionStrategy:MergeBranchesBySquash' :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy = Maybe ConflictResolutionStrategyTypeEnum
a} :: MergeBranchesBySquash)

-- | The email address of the person merging the branches. This information
-- is used in the commit information for the merge.
mergeBranchesBySquash_email :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe Prelude.Text)
mergeBranchesBySquash_email :: Lens' MergeBranchesBySquash (Maybe Text)
mergeBranchesBySquash_email = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe Text
email :: Maybe Text
$sel:email:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
email} -> Maybe Text
email) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe Text
a -> MergeBranchesBySquash
s {$sel:email:MergeBranchesBySquash' :: Maybe Text
email = Maybe Text
a} :: MergeBranchesBySquash)

-- | If the commit contains deletions, whether to keep a folder or folder
-- structure if the changes leave the folders empty. If this is specified
-- as true, a .gitkeep file is created for empty folders. The default is
-- false.
mergeBranchesBySquash_keepEmptyFolders :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe Prelude.Bool)
mergeBranchesBySquash_keepEmptyFolders :: Lens' MergeBranchesBySquash (Maybe Bool)
mergeBranchesBySquash_keepEmptyFolders = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe Bool
keepEmptyFolders :: Maybe Bool
$sel:keepEmptyFolders:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Bool
keepEmptyFolders} -> Maybe Bool
keepEmptyFolders) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe Bool
a -> MergeBranchesBySquash
s {$sel:keepEmptyFolders:MergeBranchesBySquash' :: Maybe Bool
keepEmptyFolders = Maybe Bool
a} :: MergeBranchesBySquash)

-- | The branch where the merge is applied.
mergeBranchesBySquash_targetBranch :: Lens.Lens' MergeBranchesBySquash (Prelude.Maybe Prelude.Text)
mergeBranchesBySquash_targetBranch :: Lens' MergeBranchesBySquash (Maybe Text)
mergeBranchesBySquash_targetBranch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Maybe Text
targetBranch :: Maybe Text
$sel:targetBranch:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
targetBranch} -> Maybe Text
targetBranch) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Maybe Text
a -> MergeBranchesBySquash
s {$sel:targetBranch:MergeBranchesBySquash' :: Maybe Text
targetBranch = Maybe Text
a} :: MergeBranchesBySquash)

-- | The name of the repository where you want to merge two branches.
mergeBranchesBySquash_repositoryName :: Lens.Lens' MergeBranchesBySquash Prelude.Text
mergeBranchesBySquash_repositoryName :: Lens' MergeBranchesBySquash Text
mergeBranchesBySquash_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Text
repositoryName :: Text
$sel:repositoryName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
repositoryName} -> Text
repositoryName) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Text
a -> MergeBranchesBySquash
s {$sel:repositoryName:MergeBranchesBySquash' :: Text
repositoryName = Text
a} :: MergeBranchesBySquash)

-- | The branch, tag, HEAD, or other fully qualified reference used to
-- identify a commit (for example, a branch name or a full commit ID).
mergeBranchesBySquash_sourceCommitSpecifier :: Lens.Lens' MergeBranchesBySquash Prelude.Text
mergeBranchesBySquash_sourceCommitSpecifier :: Lens' MergeBranchesBySquash Text
mergeBranchesBySquash_sourceCommitSpecifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Text
sourceCommitSpecifier :: Text
$sel:sourceCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
sourceCommitSpecifier} -> Text
sourceCommitSpecifier) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Text
a -> MergeBranchesBySquash
s {$sel:sourceCommitSpecifier:MergeBranchesBySquash' :: Text
sourceCommitSpecifier = Text
a} :: MergeBranchesBySquash)

-- | The branch, tag, HEAD, or other fully qualified reference used to
-- identify a commit (for example, a branch name or a full commit ID).
mergeBranchesBySquash_destinationCommitSpecifier :: Lens.Lens' MergeBranchesBySquash Prelude.Text
mergeBranchesBySquash_destinationCommitSpecifier :: Lens' MergeBranchesBySquash Text
mergeBranchesBySquash_destinationCommitSpecifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquash' {Text
destinationCommitSpecifier :: Text
$sel:destinationCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
destinationCommitSpecifier} -> Text
destinationCommitSpecifier) (\s :: MergeBranchesBySquash
s@MergeBranchesBySquash' {} Text
a -> MergeBranchesBySquash
s {$sel:destinationCommitSpecifier:MergeBranchesBySquash' :: Text
destinationCommitSpecifier = Text
a} :: MergeBranchesBySquash)

instance Core.AWSRequest MergeBranchesBySquash where
  type
    AWSResponse MergeBranchesBySquash =
      MergeBranchesBySquashResponse
  request :: (Service -> Service)
-> MergeBranchesBySquash -> Request MergeBranchesBySquash
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 MergeBranchesBySquash
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse MergeBranchesBySquash)))
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 -> Maybe Text -> Int -> MergeBranchesBySquashResponse
MergeBranchesBySquashResponse'
            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
"commitId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"treeId")
            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 MergeBranchesBySquash where
  hashWithSalt :: Int -> MergeBranchesBySquash -> Int
hashWithSalt Int
_salt MergeBranchesBySquash' {Maybe Bool
Maybe Text
Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Maybe ConflictResolution
Text
destinationCommitSpecifier :: Text
sourceCommitSpecifier :: Text
repositoryName :: Text
targetBranch :: Maybe Text
keepEmptyFolders :: Maybe Bool
email :: Maybe Text
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolution :: Maybe ConflictResolution
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
commitMessage :: Maybe Text
authorName :: Maybe Text
$sel:destinationCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:sourceCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:repositoryName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:targetBranch:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:keepEmptyFolders:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Bool
$sel:email:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:conflictResolutionStrategy:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictResolution:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolution
$sel:conflictDetailLevel:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictDetailLevelTypeEnum
$sel:commitMessage:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:authorName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
authorName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
commitMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConflictResolution
conflictResolution
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
email
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
keepEmptyFolders
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetBranch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
repositoryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceCommitSpecifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
destinationCommitSpecifier

instance Prelude.NFData MergeBranchesBySquash where
  rnf :: MergeBranchesBySquash -> ()
rnf MergeBranchesBySquash' {Maybe Bool
Maybe Text
Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Maybe ConflictResolution
Text
destinationCommitSpecifier :: Text
sourceCommitSpecifier :: Text
repositoryName :: Text
targetBranch :: Maybe Text
keepEmptyFolders :: Maybe Bool
email :: Maybe Text
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolution :: Maybe ConflictResolution
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
commitMessage :: Maybe Text
authorName :: Maybe Text
$sel:destinationCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:sourceCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:repositoryName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:targetBranch:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:keepEmptyFolders:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Bool
$sel:email:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:conflictResolutionStrategy:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictResolution:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolution
$sel:conflictDetailLevel:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictDetailLevelTypeEnum
$sel:commitMessage:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:authorName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authorName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
commitMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConflictResolution
conflictResolution
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
email
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
keepEmptyFolders
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetBranch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
repositoryName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceCommitSpecifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
destinationCommitSpecifier

instance Data.ToHeaders MergeBranchesBySquash where
  toHeaders :: MergeBranchesBySquash -> 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.MergeBranchesBySquash" ::
                          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 MergeBranchesBySquash where
  toJSON :: MergeBranchesBySquash -> Value
toJSON MergeBranchesBySquash' {Maybe Bool
Maybe Text
Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Maybe ConflictResolution
Text
destinationCommitSpecifier :: Text
sourceCommitSpecifier :: Text
repositoryName :: Text
targetBranch :: Maybe Text
keepEmptyFolders :: Maybe Bool
email :: Maybe Text
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolution :: Maybe ConflictResolution
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
commitMessage :: Maybe Text
authorName :: Maybe Text
$sel:destinationCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:sourceCommitSpecifier:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:repositoryName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Text
$sel:targetBranch:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:keepEmptyFolders:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Bool
$sel:email:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:conflictResolutionStrategy:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictResolution:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictResolution
$sel:conflictDetailLevel:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe ConflictDetailLevelTypeEnum
$sel:commitMessage:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
$sel:authorName:MergeBranchesBySquash' :: MergeBranchesBySquash -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"authorName" 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
authorName,
            (Key
"commitMessage" 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
commitMessage,
            (Key
"conflictDetailLevel" 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 ConflictDetailLevelTypeEnum
conflictDetailLevel,
            (Key
"conflictResolution" 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 ConflictResolution
conflictResolution,
            (Key
"conflictResolutionStrategy" 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 ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy,
            (Key
"email" 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
email,
            (Key
"keepEmptyFolders" 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 Bool
keepEmptyFolders,
            (Key
"targetBranch" 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
targetBranch,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"repositoryName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
repositoryName),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"sourceCommitSpecifier"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sourceCommitSpecifier
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"destinationCommitSpecifier"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
destinationCommitSpecifier
              )
          ]
      )

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

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

-- | /See:/ 'newMergeBranchesBySquashResponse' smart constructor.
data MergeBranchesBySquashResponse = MergeBranchesBySquashResponse'
  { -- | The commit ID of the merge in the destination or target branch.
    MergeBranchesBySquashResponse -> Maybe Text
commitId :: Prelude.Maybe Prelude.Text,
    -- | The tree ID of the merge in the destination or target branch.
    MergeBranchesBySquashResponse -> Maybe Text
treeId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    MergeBranchesBySquashResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (MergeBranchesBySquashResponse
-> MergeBranchesBySquashResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MergeBranchesBySquashResponse
-> MergeBranchesBySquashResponse -> Bool
$c/= :: MergeBranchesBySquashResponse
-> MergeBranchesBySquashResponse -> Bool
== :: MergeBranchesBySquashResponse
-> MergeBranchesBySquashResponse -> Bool
$c== :: MergeBranchesBySquashResponse
-> MergeBranchesBySquashResponse -> Bool
Prelude.Eq, ReadPrec [MergeBranchesBySquashResponse]
ReadPrec MergeBranchesBySquashResponse
Int -> ReadS MergeBranchesBySquashResponse
ReadS [MergeBranchesBySquashResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MergeBranchesBySquashResponse]
$creadListPrec :: ReadPrec [MergeBranchesBySquashResponse]
readPrec :: ReadPrec MergeBranchesBySquashResponse
$creadPrec :: ReadPrec MergeBranchesBySquashResponse
readList :: ReadS [MergeBranchesBySquashResponse]
$creadList :: ReadS [MergeBranchesBySquashResponse]
readsPrec :: Int -> ReadS MergeBranchesBySquashResponse
$creadsPrec :: Int -> ReadS MergeBranchesBySquashResponse
Prelude.Read, Int -> MergeBranchesBySquashResponse -> ShowS
[MergeBranchesBySquashResponse] -> ShowS
MergeBranchesBySquashResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MergeBranchesBySquashResponse] -> ShowS
$cshowList :: [MergeBranchesBySquashResponse] -> ShowS
show :: MergeBranchesBySquashResponse -> String
$cshow :: MergeBranchesBySquashResponse -> String
showsPrec :: Int -> MergeBranchesBySquashResponse -> ShowS
$cshowsPrec :: Int -> MergeBranchesBySquashResponse -> ShowS
Prelude.Show, forall x.
Rep MergeBranchesBySquashResponse x
-> MergeBranchesBySquashResponse
forall x.
MergeBranchesBySquashResponse
-> Rep MergeBranchesBySquashResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep MergeBranchesBySquashResponse x
-> MergeBranchesBySquashResponse
$cfrom :: forall x.
MergeBranchesBySquashResponse
-> Rep MergeBranchesBySquashResponse x
Prelude.Generic)

-- |
-- Create a value of 'MergeBranchesBySquashResponse' 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:
--
-- 'commitId', 'mergeBranchesBySquashResponse_commitId' - The commit ID of the merge in the destination or target branch.
--
-- 'treeId', 'mergeBranchesBySquashResponse_treeId' - The tree ID of the merge in the destination or target branch.
--
-- 'httpStatus', 'mergeBranchesBySquashResponse_httpStatus' - The response's http status code.
newMergeBranchesBySquashResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  MergeBranchesBySquashResponse
newMergeBranchesBySquashResponse :: Int -> MergeBranchesBySquashResponse
newMergeBranchesBySquashResponse Int
pHttpStatus_ =
  MergeBranchesBySquashResponse'
    { $sel:commitId:MergeBranchesBySquashResponse' :: Maybe Text
commitId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:treeId:MergeBranchesBySquashResponse' :: Maybe Text
treeId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:MergeBranchesBySquashResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The commit ID of the merge in the destination or target branch.
mergeBranchesBySquashResponse_commitId :: Lens.Lens' MergeBranchesBySquashResponse (Prelude.Maybe Prelude.Text)
mergeBranchesBySquashResponse_commitId :: Lens' MergeBranchesBySquashResponse (Maybe Text)
mergeBranchesBySquashResponse_commitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquashResponse' {Maybe Text
commitId :: Maybe Text
$sel:commitId:MergeBranchesBySquashResponse' :: MergeBranchesBySquashResponse -> Maybe Text
commitId} -> Maybe Text
commitId) (\s :: MergeBranchesBySquashResponse
s@MergeBranchesBySquashResponse' {} Maybe Text
a -> MergeBranchesBySquashResponse
s {$sel:commitId:MergeBranchesBySquashResponse' :: Maybe Text
commitId = Maybe Text
a} :: MergeBranchesBySquashResponse)

-- | The tree ID of the merge in the destination or target branch.
mergeBranchesBySquashResponse_treeId :: Lens.Lens' MergeBranchesBySquashResponse (Prelude.Maybe Prelude.Text)
mergeBranchesBySquashResponse_treeId :: Lens' MergeBranchesBySquashResponse (Maybe Text)
mergeBranchesBySquashResponse_treeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MergeBranchesBySquashResponse' {Maybe Text
treeId :: Maybe Text
$sel:treeId:MergeBranchesBySquashResponse' :: MergeBranchesBySquashResponse -> Maybe Text
treeId} -> Maybe Text
treeId) (\s :: MergeBranchesBySquashResponse
s@MergeBranchesBySquashResponse' {} Maybe Text
a -> MergeBranchesBySquashResponse
s {$sel:treeId:MergeBranchesBySquashResponse' :: Maybe Text
treeId = Maybe Text
a} :: MergeBranchesBySquashResponse)

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

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