{-# 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.GetMergeCommit
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a specified merge commit.
module Amazonka.CodeCommit.GetMergeCommit
  ( -- * Creating a Request
    GetMergeCommit (..),
    newGetMergeCommit,

    -- * Request Lenses
    getMergeCommit_conflictDetailLevel,
    getMergeCommit_conflictResolutionStrategy,
    getMergeCommit_repositoryName,
    getMergeCommit_sourceCommitSpecifier,
    getMergeCommit_destinationCommitSpecifier,

    -- * Destructuring the Response
    GetMergeCommitResponse (..),
    newGetMergeCommitResponse,

    -- * Response Lenses
    getMergeCommitResponse_baseCommitId,
    getMergeCommitResponse_destinationCommitId,
    getMergeCommitResponse_mergedCommitId,
    getMergeCommitResponse_sourceCommitId,
    getMergeCommitResponse_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:/ 'newGetMergeCommit' smart constructor.
data GetMergeCommit = GetMergeCommit'
  { -- | 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.
    GetMergeCommit -> Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel :: Prelude.Maybe ConflictDetailLevelTypeEnum,
    -- | 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.
    GetMergeCommit -> Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy :: Prelude.Maybe ConflictResolutionStrategyTypeEnum,
    -- | The name of the repository that contains the merge commit about which
    -- you want to get information.
    GetMergeCommit -> 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).
    GetMergeCommit -> 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).
    GetMergeCommit -> Text
destinationCommitSpecifier :: Prelude.Text
  }
  deriving (GetMergeCommit -> GetMergeCommit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMergeCommit -> GetMergeCommit -> Bool
$c/= :: GetMergeCommit -> GetMergeCommit -> Bool
== :: GetMergeCommit -> GetMergeCommit -> Bool
$c== :: GetMergeCommit -> GetMergeCommit -> Bool
Prelude.Eq, ReadPrec [GetMergeCommit]
ReadPrec GetMergeCommit
Int -> ReadS GetMergeCommit
ReadS [GetMergeCommit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMergeCommit]
$creadListPrec :: ReadPrec [GetMergeCommit]
readPrec :: ReadPrec GetMergeCommit
$creadPrec :: ReadPrec GetMergeCommit
readList :: ReadS [GetMergeCommit]
$creadList :: ReadS [GetMergeCommit]
readsPrec :: Int -> ReadS GetMergeCommit
$creadsPrec :: Int -> ReadS GetMergeCommit
Prelude.Read, Int -> GetMergeCommit -> ShowS
[GetMergeCommit] -> ShowS
GetMergeCommit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMergeCommit] -> ShowS
$cshowList :: [GetMergeCommit] -> ShowS
show :: GetMergeCommit -> String
$cshow :: GetMergeCommit -> String
showsPrec :: Int -> GetMergeCommit -> ShowS
$cshowsPrec :: Int -> GetMergeCommit -> ShowS
Prelude.Show, forall x. Rep GetMergeCommit x -> GetMergeCommit
forall x. GetMergeCommit -> Rep GetMergeCommit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMergeCommit x -> GetMergeCommit
$cfrom :: forall x. GetMergeCommit -> Rep GetMergeCommit x
Prelude.Generic)

-- |
-- Create a value of 'GetMergeCommit' 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:
--
-- 'conflictDetailLevel', 'getMergeCommit_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.
--
-- 'conflictResolutionStrategy', 'getMergeCommit_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.
--
-- 'repositoryName', 'getMergeCommit_repositoryName' - The name of the repository that contains the merge commit about which
-- you want to get information.
--
-- 'sourceCommitSpecifier', 'getMergeCommit_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', 'getMergeCommit_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).
newGetMergeCommit ::
  -- | 'repositoryName'
  Prelude.Text ->
  -- | 'sourceCommitSpecifier'
  Prelude.Text ->
  -- | 'destinationCommitSpecifier'
  Prelude.Text ->
  GetMergeCommit
newGetMergeCommit :: Text -> Text -> Text -> GetMergeCommit
newGetMergeCommit
  Text
pRepositoryName_
  Text
pSourceCommitSpecifier_
  Text
pDestinationCommitSpecifier_ =
    GetMergeCommit'
      { $sel:conflictDetailLevel:GetMergeCommit' :: Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel =
          forall a. Maybe a
Prelude.Nothing,
        $sel:conflictResolutionStrategy:GetMergeCommit' :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy = forall a. Maybe a
Prelude.Nothing,
        $sel:repositoryName:GetMergeCommit' :: Text
repositoryName = Text
pRepositoryName_,
        $sel:sourceCommitSpecifier:GetMergeCommit' :: Text
sourceCommitSpecifier = Text
pSourceCommitSpecifier_,
        $sel:destinationCommitSpecifier:GetMergeCommit' :: Text
destinationCommitSpecifier =
          Text
pDestinationCommitSpecifier_
      }

-- | 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.
getMergeCommit_conflictDetailLevel :: Lens.Lens' GetMergeCommit (Prelude.Maybe ConflictDetailLevelTypeEnum)
getMergeCommit_conflictDetailLevel :: Lens' GetMergeCommit (Maybe ConflictDetailLevelTypeEnum)
getMergeCommit_conflictDetailLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeCommit' {Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:conflictDetailLevel:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel} -> Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel) (\s :: GetMergeCommit
s@GetMergeCommit' {} Maybe ConflictDetailLevelTypeEnum
a -> GetMergeCommit
s {$sel:conflictDetailLevel:GetMergeCommit' :: Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel = Maybe ConflictDetailLevelTypeEnum
a} :: GetMergeCommit)

-- | 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.
getMergeCommit_conflictResolutionStrategy :: Lens.Lens' GetMergeCommit (Prelude.Maybe ConflictResolutionStrategyTypeEnum)
getMergeCommit_conflictResolutionStrategy :: Lens' GetMergeCommit (Maybe ConflictResolutionStrategyTypeEnum)
getMergeCommit_conflictResolutionStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeCommit' {Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictResolutionStrategy:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy} -> Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy) (\s :: GetMergeCommit
s@GetMergeCommit' {} Maybe ConflictResolutionStrategyTypeEnum
a -> GetMergeCommit
s {$sel:conflictResolutionStrategy:GetMergeCommit' :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy = Maybe ConflictResolutionStrategyTypeEnum
a} :: GetMergeCommit)

-- | The name of the repository that contains the merge commit about which
-- you want to get information.
getMergeCommit_repositoryName :: Lens.Lens' GetMergeCommit Prelude.Text
getMergeCommit_repositoryName :: Lens' GetMergeCommit Text
getMergeCommit_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeCommit' {Text
repositoryName :: Text
$sel:repositoryName:GetMergeCommit' :: GetMergeCommit -> Text
repositoryName} -> Text
repositoryName) (\s :: GetMergeCommit
s@GetMergeCommit' {} Text
a -> GetMergeCommit
s {$sel:repositoryName:GetMergeCommit' :: Text
repositoryName = Text
a} :: GetMergeCommit)

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

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

instance Core.AWSRequest GetMergeCommit where
  type
    AWSResponse GetMergeCommit =
      GetMergeCommitResponse
  request :: (Service -> Service) -> GetMergeCommit -> Request GetMergeCommit
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 GetMergeCommit
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetMergeCommit)))
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
-> Maybe Text
-> Maybe Text
-> Int
-> GetMergeCommitResponse
GetMergeCommitResponse'
            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
"baseCommitId")
            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
"destinationCommitId")
            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
"mergedCommitId")
            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
"sourceCommitId")
            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 GetMergeCommit where
  hashWithSalt :: Int -> GetMergeCommit -> Int
hashWithSalt Int
_salt GetMergeCommit' {Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Text
destinationCommitSpecifier :: Text
sourceCommitSpecifier :: Text
repositoryName :: Text
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:destinationCommitSpecifier:GetMergeCommit' :: GetMergeCommit -> Text
$sel:sourceCommitSpecifier:GetMergeCommit' :: GetMergeCommit -> Text
$sel:repositoryName:GetMergeCommit' :: GetMergeCommit -> Text
$sel:conflictResolutionStrategy:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictDetailLevel:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictDetailLevelTypeEnum
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy
      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 GetMergeCommit where
  rnf :: GetMergeCommit -> ()
rnf GetMergeCommit' {Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Text
destinationCommitSpecifier :: Text
sourceCommitSpecifier :: Text
repositoryName :: Text
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:destinationCommitSpecifier:GetMergeCommit' :: GetMergeCommit -> Text
$sel:sourceCommitSpecifier:GetMergeCommit' :: GetMergeCommit -> Text
$sel:repositoryName:GetMergeCommit' :: GetMergeCommit -> Text
$sel:conflictResolutionStrategy:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictDetailLevel:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictDetailLevelTypeEnum
..} =
    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 ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy
      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 GetMergeCommit where
  toHeaders :: GetMergeCommit -> 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.GetMergeCommit" ::
                          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 GetMergeCommit where
  toJSON :: GetMergeCommit -> Value
toJSON GetMergeCommit' {Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Text
destinationCommitSpecifier :: Text
sourceCommitSpecifier :: Text
repositoryName :: Text
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:destinationCommitSpecifier:GetMergeCommit' :: GetMergeCommit -> Text
$sel:sourceCommitSpecifier:GetMergeCommit' :: GetMergeCommit -> Text
$sel:repositoryName:GetMergeCommit' :: GetMergeCommit -> Text
$sel:conflictResolutionStrategy:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictDetailLevel:GetMergeCommit' :: GetMergeCommit -> Maybe ConflictDetailLevelTypeEnum
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"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,
            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 GetMergeCommit where
  toPath :: GetMergeCommit -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetMergeCommitResponse' smart constructor.
data GetMergeCommitResponse = GetMergeCommitResponse'
  { -- | The commit ID of the merge base.
    GetMergeCommitResponse -> Maybe Text
baseCommitId :: Prelude.Maybe Prelude.Text,
    -- | The commit ID of the destination commit specifier that was used in the
    -- merge evaluation.
    GetMergeCommitResponse -> Maybe Text
destinationCommitId :: Prelude.Maybe Prelude.Text,
    -- | The commit ID for the merge commit created when the source branch was
    -- merged into the destination branch. If the fast-forward merge strategy
    -- was used, there is no merge commit.
    GetMergeCommitResponse -> Maybe Text
mergedCommitId :: Prelude.Maybe Prelude.Text,
    -- | The commit ID of the source commit specifier that was used in the merge
    -- evaluation.
    GetMergeCommitResponse -> Maybe Text
sourceCommitId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetMergeCommitResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetMergeCommitResponse -> GetMergeCommitResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMergeCommitResponse -> GetMergeCommitResponse -> Bool
$c/= :: GetMergeCommitResponse -> GetMergeCommitResponse -> Bool
== :: GetMergeCommitResponse -> GetMergeCommitResponse -> Bool
$c== :: GetMergeCommitResponse -> GetMergeCommitResponse -> Bool
Prelude.Eq, ReadPrec [GetMergeCommitResponse]
ReadPrec GetMergeCommitResponse
Int -> ReadS GetMergeCommitResponse
ReadS [GetMergeCommitResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMergeCommitResponse]
$creadListPrec :: ReadPrec [GetMergeCommitResponse]
readPrec :: ReadPrec GetMergeCommitResponse
$creadPrec :: ReadPrec GetMergeCommitResponse
readList :: ReadS [GetMergeCommitResponse]
$creadList :: ReadS [GetMergeCommitResponse]
readsPrec :: Int -> ReadS GetMergeCommitResponse
$creadsPrec :: Int -> ReadS GetMergeCommitResponse
Prelude.Read, Int -> GetMergeCommitResponse -> ShowS
[GetMergeCommitResponse] -> ShowS
GetMergeCommitResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMergeCommitResponse] -> ShowS
$cshowList :: [GetMergeCommitResponse] -> ShowS
show :: GetMergeCommitResponse -> String
$cshow :: GetMergeCommitResponse -> String
showsPrec :: Int -> GetMergeCommitResponse -> ShowS
$cshowsPrec :: Int -> GetMergeCommitResponse -> ShowS
Prelude.Show, forall x. Rep GetMergeCommitResponse x -> GetMergeCommitResponse
forall x. GetMergeCommitResponse -> Rep GetMergeCommitResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMergeCommitResponse x -> GetMergeCommitResponse
$cfrom :: forall x. GetMergeCommitResponse -> Rep GetMergeCommitResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMergeCommitResponse' 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:
--
-- 'baseCommitId', 'getMergeCommitResponse_baseCommitId' - The commit ID of the merge base.
--
-- 'destinationCommitId', 'getMergeCommitResponse_destinationCommitId' - The commit ID of the destination commit specifier that was used in the
-- merge evaluation.
--
-- 'mergedCommitId', 'getMergeCommitResponse_mergedCommitId' - The commit ID for the merge commit created when the source branch was
-- merged into the destination branch. If the fast-forward merge strategy
-- was used, there is no merge commit.
--
-- 'sourceCommitId', 'getMergeCommitResponse_sourceCommitId' - The commit ID of the source commit specifier that was used in the merge
-- evaluation.
--
-- 'httpStatus', 'getMergeCommitResponse_httpStatus' - The response's http status code.
newGetMergeCommitResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMergeCommitResponse
newGetMergeCommitResponse :: Int -> GetMergeCommitResponse
newGetMergeCommitResponse Int
pHttpStatus_ =
  GetMergeCommitResponse'
    { $sel:baseCommitId:GetMergeCommitResponse' :: Maybe Text
baseCommitId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:destinationCommitId:GetMergeCommitResponse' :: Maybe Text
destinationCommitId = forall a. Maybe a
Prelude.Nothing,
      $sel:mergedCommitId:GetMergeCommitResponse' :: Maybe Text
mergedCommitId = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceCommitId:GetMergeCommitResponse' :: Maybe Text
sourceCommitId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetMergeCommitResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The commit ID of the merge base.
getMergeCommitResponse_baseCommitId :: Lens.Lens' GetMergeCommitResponse (Prelude.Maybe Prelude.Text)
getMergeCommitResponse_baseCommitId :: Lens' GetMergeCommitResponse (Maybe Text)
getMergeCommitResponse_baseCommitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeCommitResponse' {Maybe Text
baseCommitId :: Maybe Text
$sel:baseCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
baseCommitId} -> Maybe Text
baseCommitId) (\s :: GetMergeCommitResponse
s@GetMergeCommitResponse' {} Maybe Text
a -> GetMergeCommitResponse
s {$sel:baseCommitId:GetMergeCommitResponse' :: Maybe Text
baseCommitId = Maybe Text
a} :: GetMergeCommitResponse)

-- | The commit ID of the destination commit specifier that was used in the
-- merge evaluation.
getMergeCommitResponse_destinationCommitId :: Lens.Lens' GetMergeCommitResponse (Prelude.Maybe Prelude.Text)
getMergeCommitResponse_destinationCommitId :: Lens' GetMergeCommitResponse (Maybe Text)
getMergeCommitResponse_destinationCommitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeCommitResponse' {Maybe Text
destinationCommitId :: Maybe Text
$sel:destinationCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
destinationCommitId} -> Maybe Text
destinationCommitId) (\s :: GetMergeCommitResponse
s@GetMergeCommitResponse' {} Maybe Text
a -> GetMergeCommitResponse
s {$sel:destinationCommitId:GetMergeCommitResponse' :: Maybe Text
destinationCommitId = Maybe Text
a} :: GetMergeCommitResponse)

-- | The commit ID for the merge commit created when the source branch was
-- merged into the destination branch. If the fast-forward merge strategy
-- was used, there is no merge commit.
getMergeCommitResponse_mergedCommitId :: Lens.Lens' GetMergeCommitResponse (Prelude.Maybe Prelude.Text)
getMergeCommitResponse_mergedCommitId :: Lens' GetMergeCommitResponse (Maybe Text)
getMergeCommitResponse_mergedCommitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeCommitResponse' {Maybe Text
mergedCommitId :: Maybe Text
$sel:mergedCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
mergedCommitId} -> Maybe Text
mergedCommitId) (\s :: GetMergeCommitResponse
s@GetMergeCommitResponse' {} Maybe Text
a -> GetMergeCommitResponse
s {$sel:mergedCommitId:GetMergeCommitResponse' :: Maybe Text
mergedCommitId = Maybe Text
a} :: GetMergeCommitResponse)

-- | The commit ID of the source commit specifier that was used in the merge
-- evaluation.
getMergeCommitResponse_sourceCommitId :: Lens.Lens' GetMergeCommitResponse (Prelude.Maybe Prelude.Text)
getMergeCommitResponse_sourceCommitId :: Lens' GetMergeCommitResponse (Maybe Text)
getMergeCommitResponse_sourceCommitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeCommitResponse' {Maybe Text
sourceCommitId :: Maybe Text
$sel:sourceCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
sourceCommitId} -> Maybe Text
sourceCommitId) (\s :: GetMergeCommitResponse
s@GetMergeCommitResponse' {} Maybe Text
a -> GetMergeCommitResponse
s {$sel:sourceCommitId:GetMergeCommitResponse' :: Maybe Text
sourceCommitId = Maybe Text
a} :: GetMergeCommitResponse)

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

instance Prelude.NFData GetMergeCommitResponse where
  rnf :: GetMergeCommitResponse -> ()
rnf GetMergeCommitResponse' {Int
Maybe Text
httpStatus :: Int
sourceCommitId :: Maybe Text
mergedCommitId :: Maybe Text
destinationCommitId :: Maybe Text
baseCommitId :: Maybe Text
$sel:httpStatus:GetMergeCommitResponse' :: GetMergeCommitResponse -> Int
$sel:sourceCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
$sel:mergedCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
$sel:destinationCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
$sel:baseCommitId:GetMergeCommitResponse' :: GetMergeCommitResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baseCommitId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationCommitId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
mergedCommitId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceCommitId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus