{-# 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.GetMergeConflicts
-- 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 merge conflicts between the before and after
-- commit IDs for a pull request in a repository.
module Amazonka.CodeCommit.GetMergeConflicts
  ( -- * Creating a Request
    GetMergeConflicts (..),
    newGetMergeConflicts,

    -- * Request Lenses
    getMergeConflicts_conflictDetailLevel,
    getMergeConflicts_conflictResolutionStrategy,
    getMergeConflicts_maxConflictFiles,
    getMergeConflicts_nextToken,
    getMergeConflicts_repositoryName,
    getMergeConflicts_destinationCommitSpecifier,
    getMergeConflicts_sourceCommitSpecifier,
    getMergeConflicts_mergeOption,

    -- * Destructuring the Response
    GetMergeConflictsResponse (..),
    newGetMergeConflictsResponse,

    -- * Response Lenses
    getMergeConflictsResponse_baseCommitId,
    getMergeConflictsResponse_nextToken,
    getMergeConflictsResponse_httpStatus,
    getMergeConflictsResponse_mergeable,
    getMergeConflictsResponse_destinationCommitId,
    getMergeConflictsResponse_sourceCommitId,
    getMergeConflictsResponse_conflictMetadataList,
  )
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:/ 'newGetMergeConflicts' smart constructor.
data GetMergeConflicts = GetMergeConflicts'
  { -- | 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.
    GetMergeConflicts -> 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.
    GetMergeConflicts -> Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy :: Prelude.Maybe ConflictResolutionStrategyTypeEnum,
    -- | The maximum number of files to include in the output.
    GetMergeConflicts -> Maybe Int
maxConflictFiles :: Prelude.Maybe Prelude.Int,
    -- | An enumeration token that, when provided in a request, returns the next
    -- batch of the results.
    GetMergeConflicts -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the repository where the pull request was created.
    GetMergeConflicts -> 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).
    GetMergeConflicts -> Text
destinationCommitSpecifier :: 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).
    GetMergeConflicts -> Text
sourceCommitSpecifier :: Prelude.Text,
    -- | The merge option or strategy you want to use to merge the code.
    GetMergeConflicts -> MergeOptionTypeEnum
mergeOption :: MergeOptionTypeEnum
  }
  deriving (GetMergeConflicts -> GetMergeConflicts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMergeConflicts -> GetMergeConflicts -> Bool
$c/= :: GetMergeConflicts -> GetMergeConflicts -> Bool
== :: GetMergeConflicts -> GetMergeConflicts -> Bool
$c== :: GetMergeConflicts -> GetMergeConflicts -> Bool
Prelude.Eq, ReadPrec [GetMergeConflicts]
ReadPrec GetMergeConflicts
Int -> ReadS GetMergeConflicts
ReadS [GetMergeConflicts]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMergeConflicts]
$creadListPrec :: ReadPrec [GetMergeConflicts]
readPrec :: ReadPrec GetMergeConflicts
$creadPrec :: ReadPrec GetMergeConflicts
readList :: ReadS [GetMergeConflicts]
$creadList :: ReadS [GetMergeConflicts]
readsPrec :: Int -> ReadS GetMergeConflicts
$creadsPrec :: Int -> ReadS GetMergeConflicts
Prelude.Read, Int -> GetMergeConflicts -> ShowS
[GetMergeConflicts] -> ShowS
GetMergeConflicts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMergeConflicts] -> ShowS
$cshowList :: [GetMergeConflicts] -> ShowS
show :: GetMergeConflicts -> String
$cshow :: GetMergeConflicts -> String
showsPrec :: Int -> GetMergeConflicts -> ShowS
$cshowsPrec :: Int -> GetMergeConflicts -> ShowS
Prelude.Show, forall x. Rep GetMergeConflicts x -> GetMergeConflicts
forall x. GetMergeConflicts -> Rep GetMergeConflicts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMergeConflicts x -> GetMergeConflicts
$cfrom :: forall x. GetMergeConflicts -> Rep GetMergeConflicts x
Prelude.Generic)

-- |
-- Create a value of 'GetMergeConflicts' 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', 'getMergeConflicts_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', 'getMergeConflicts_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.
--
-- 'maxConflictFiles', 'getMergeConflicts_maxConflictFiles' - The maximum number of files to include in the output.
--
-- 'nextToken', 'getMergeConflicts_nextToken' - An enumeration token that, when provided in a request, returns the next
-- batch of the results.
--
-- 'repositoryName', 'getMergeConflicts_repositoryName' - The name of the repository where the pull request was created.
--
-- 'destinationCommitSpecifier', 'getMergeConflicts_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).
--
-- 'sourceCommitSpecifier', 'getMergeConflicts_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).
--
-- 'mergeOption', 'getMergeConflicts_mergeOption' - The merge option or strategy you want to use to merge the code.
newGetMergeConflicts ::
  -- | 'repositoryName'
  Prelude.Text ->
  -- | 'destinationCommitSpecifier'
  Prelude.Text ->
  -- | 'sourceCommitSpecifier'
  Prelude.Text ->
  -- | 'mergeOption'
  MergeOptionTypeEnum ->
  GetMergeConflicts
newGetMergeConflicts :: Text -> Text -> Text -> MergeOptionTypeEnum -> GetMergeConflicts
newGetMergeConflicts
  Text
pRepositoryName_
  Text
pDestinationCommitSpecifier_
  Text
pSourceCommitSpecifier_
  MergeOptionTypeEnum
pMergeOption_ =
    GetMergeConflicts'
      { $sel:conflictDetailLevel:GetMergeConflicts' :: Maybe ConflictDetailLevelTypeEnum
conflictDetailLevel =
          forall a. Maybe a
Prelude.Nothing,
        $sel:conflictResolutionStrategy:GetMergeConflicts' :: Maybe ConflictResolutionStrategyTypeEnum
conflictResolutionStrategy = forall a. Maybe a
Prelude.Nothing,
        $sel:maxConflictFiles:GetMergeConflicts' :: Maybe Int
maxConflictFiles = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetMergeConflicts' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:repositoryName:GetMergeConflicts' :: Text
repositoryName = Text
pRepositoryName_,
        $sel:destinationCommitSpecifier:GetMergeConflicts' :: Text
destinationCommitSpecifier =
          Text
pDestinationCommitSpecifier_,
        $sel:sourceCommitSpecifier:GetMergeConflicts' :: Text
sourceCommitSpecifier = Text
pSourceCommitSpecifier_,
        $sel:mergeOption:GetMergeConflicts' :: MergeOptionTypeEnum
mergeOption = MergeOptionTypeEnum
pMergeOption_
      }

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

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

-- | The maximum number of files to include in the output.
getMergeConflicts_maxConflictFiles :: Lens.Lens' GetMergeConflicts (Prelude.Maybe Prelude.Int)
getMergeConflicts_maxConflictFiles :: Lens' GetMergeConflicts (Maybe Int)
getMergeConflicts_maxConflictFiles = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeConflicts' {Maybe Int
maxConflictFiles :: Maybe Int
$sel:maxConflictFiles:GetMergeConflicts' :: GetMergeConflicts -> Maybe Int
maxConflictFiles} -> Maybe Int
maxConflictFiles) (\s :: GetMergeConflicts
s@GetMergeConflicts' {} Maybe Int
a -> GetMergeConflicts
s {$sel:maxConflictFiles:GetMergeConflicts' :: Maybe Int
maxConflictFiles = Maybe Int
a} :: GetMergeConflicts)

-- | An enumeration token that, when provided in a request, returns the next
-- batch of the results.
getMergeConflicts_nextToken :: Lens.Lens' GetMergeConflicts (Prelude.Maybe Prelude.Text)
getMergeConflicts_nextToken :: Lens' GetMergeConflicts (Maybe Text)
getMergeConflicts_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeConflicts' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetMergeConflicts' :: GetMergeConflicts -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetMergeConflicts
s@GetMergeConflicts' {} Maybe Text
a -> GetMergeConflicts
s {$sel:nextToken:GetMergeConflicts' :: Maybe Text
nextToken = Maybe Text
a} :: GetMergeConflicts)

-- | The name of the repository where the pull request was created.
getMergeConflicts_repositoryName :: Lens.Lens' GetMergeConflicts Prelude.Text
getMergeConflicts_repositoryName :: Lens' GetMergeConflicts Text
getMergeConflicts_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeConflicts' {Text
repositoryName :: Text
$sel:repositoryName:GetMergeConflicts' :: GetMergeConflicts -> Text
repositoryName} -> Text
repositoryName) (\s :: GetMergeConflicts
s@GetMergeConflicts' {} Text
a -> GetMergeConflicts
s {$sel:repositoryName:GetMergeConflicts' :: Text
repositoryName = Text
a} :: GetMergeConflicts)

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

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

-- | The merge option or strategy you want to use to merge the code.
getMergeConflicts_mergeOption :: Lens.Lens' GetMergeConflicts MergeOptionTypeEnum
getMergeConflicts_mergeOption :: Lens' GetMergeConflicts MergeOptionTypeEnum
getMergeConflicts_mergeOption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeConflicts' {MergeOptionTypeEnum
mergeOption :: MergeOptionTypeEnum
$sel:mergeOption:GetMergeConflicts' :: GetMergeConflicts -> MergeOptionTypeEnum
mergeOption} -> MergeOptionTypeEnum
mergeOption) (\s :: GetMergeConflicts
s@GetMergeConflicts' {} MergeOptionTypeEnum
a -> GetMergeConflicts
s {$sel:mergeOption:GetMergeConflicts' :: MergeOptionTypeEnum
mergeOption = MergeOptionTypeEnum
a} :: GetMergeConflicts)

instance Core.AWSRequest GetMergeConflicts where
  type
    AWSResponse GetMergeConflicts =
      GetMergeConflictsResponse
  request :: (Service -> Service)
-> GetMergeConflicts -> Request GetMergeConflicts
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 GetMergeConflicts
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetMergeConflicts)))
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
-> Bool
-> Text
-> Text
-> [ConflictMetadata]
-> GetMergeConflictsResponse
GetMergeConflictsResponse'
            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
"nextToken")
            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))
            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
"mergeable")
            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
"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 a
Data..:> Key
"sourceCommitId")
            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
"conflictMetadataList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable GetMergeConflicts where
  hashWithSalt :: Int -> GetMergeConflicts -> Int
hashWithSalt Int
_salt GetMergeConflicts' {Maybe Int
Maybe Text
Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Text
MergeOptionTypeEnum
mergeOption :: MergeOptionTypeEnum
sourceCommitSpecifier :: Text
destinationCommitSpecifier :: Text
repositoryName :: Text
nextToken :: Maybe Text
maxConflictFiles :: Maybe Int
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:mergeOption:GetMergeConflicts' :: GetMergeConflicts -> MergeOptionTypeEnum
$sel:sourceCommitSpecifier:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:destinationCommitSpecifier:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:repositoryName:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:nextToken:GetMergeConflicts' :: GetMergeConflicts -> Maybe Text
$sel:maxConflictFiles:GetMergeConflicts' :: GetMergeConflicts -> Maybe Int
$sel:conflictResolutionStrategy:GetMergeConflicts' :: GetMergeConflicts -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictDetailLevel:GetMergeConflicts' :: GetMergeConflicts -> 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` Maybe Int
maxConflictFiles
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
repositoryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
destinationCommitSpecifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceCommitSpecifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MergeOptionTypeEnum
mergeOption

instance Prelude.NFData GetMergeConflicts where
  rnf :: GetMergeConflicts -> ()
rnf GetMergeConflicts' {Maybe Int
Maybe Text
Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Text
MergeOptionTypeEnum
mergeOption :: MergeOptionTypeEnum
sourceCommitSpecifier :: Text
destinationCommitSpecifier :: Text
repositoryName :: Text
nextToken :: Maybe Text
maxConflictFiles :: Maybe Int
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:mergeOption:GetMergeConflicts' :: GetMergeConflicts -> MergeOptionTypeEnum
$sel:sourceCommitSpecifier:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:destinationCommitSpecifier:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:repositoryName:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:nextToken:GetMergeConflicts' :: GetMergeConflicts -> Maybe Text
$sel:maxConflictFiles:GetMergeConflicts' :: GetMergeConflicts -> Maybe Int
$sel:conflictResolutionStrategy:GetMergeConflicts' :: GetMergeConflicts -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictDetailLevel:GetMergeConflicts' :: GetMergeConflicts -> 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 Maybe Int
maxConflictFiles
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      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
destinationCommitSpecifier
      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 MergeOptionTypeEnum
mergeOption

instance Data.ToHeaders GetMergeConflicts where
  toHeaders :: GetMergeConflicts -> 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.GetMergeConflicts" ::
                          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 GetMergeConflicts where
  toJSON :: GetMergeConflicts -> Value
toJSON GetMergeConflicts' {Maybe Int
Maybe Text
Maybe ConflictDetailLevelTypeEnum
Maybe ConflictResolutionStrategyTypeEnum
Text
MergeOptionTypeEnum
mergeOption :: MergeOptionTypeEnum
sourceCommitSpecifier :: Text
destinationCommitSpecifier :: Text
repositoryName :: Text
nextToken :: Maybe Text
maxConflictFiles :: Maybe Int
conflictResolutionStrategy :: Maybe ConflictResolutionStrategyTypeEnum
conflictDetailLevel :: Maybe ConflictDetailLevelTypeEnum
$sel:mergeOption:GetMergeConflicts' :: GetMergeConflicts -> MergeOptionTypeEnum
$sel:sourceCommitSpecifier:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:destinationCommitSpecifier:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:repositoryName:GetMergeConflicts' :: GetMergeConflicts -> Text
$sel:nextToken:GetMergeConflicts' :: GetMergeConflicts -> Maybe Text
$sel:maxConflictFiles:GetMergeConflicts' :: GetMergeConflicts -> Maybe Int
$sel:conflictResolutionStrategy:GetMergeConflicts' :: GetMergeConflicts -> Maybe ConflictResolutionStrategyTypeEnum
$sel:conflictDetailLevel:GetMergeConflicts' :: GetMergeConflicts -> 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,
            (Key
"maxConflictFiles" 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 Int
maxConflictFiles,
            (Key
"nextToken" 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
nextToken,
            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
"destinationCommitSpecifier"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
destinationCommitSpecifier
              ),
            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
"mergeOption" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= MergeOptionTypeEnum
mergeOption)
          ]
      )

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

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

-- | /See:/ 'newGetMergeConflictsResponse' smart constructor.
data GetMergeConflictsResponse = GetMergeConflictsResponse'
  { -- | The commit ID of the merge base.
    GetMergeConflictsResponse -> Maybe Text
baseCommitId :: Prelude.Maybe Prelude.Text,
    -- | An enumeration token that can be used in a request to return the next
    -- batch of the results.
    GetMergeConflictsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetMergeConflictsResponse -> Int
httpStatus :: Prelude.Int,
    -- | A Boolean value that indicates whether the code is mergeable by the
    -- specified merge option.
    GetMergeConflictsResponse -> Bool
mergeable :: Prelude.Bool,
    -- | The commit ID of the destination commit specifier that was used in the
    -- merge evaluation.
    GetMergeConflictsResponse -> Text
destinationCommitId :: Prelude.Text,
    -- | The commit ID of the source commit specifier that was used in the merge
    -- evaluation.
    GetMergeConflictsResponse -> Text
sourceCommitId :: Prelude.Text,
    -- | A list of metadata for any conflicting files. If the specified merge
    -- strategy is FAST_FORWARD_MERGE, this list is always empty.
    GetMergeConflictsResponse -> [ConflictMetadata]
conflictMetadataList :: [ConflictMetadata]
  }
  deriving (GetMergeConflictsResponse -> GetMergeConflictsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMergeConflictsResponse -> GetMergeConflictsResponse -> Bool
$c/= :: GetMergeConflictsResponse -> GetMergeConflictsResponse -> Bool
== :: GetMergeConflictsResponse -> GetMergeConflictsResponse -> Bool
$c== :: GetMergeConflictsResponse -> GetMergeConflictsResponse -> Bool
Prelude.Eq, ReadPrec [GetMergeConflictsResponse]
ReadPrec GetMergeConflictsResponse
Int -> ReadS GetMergeConflictsResponse
ReadS [GetMergeConflictsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMergeConflictsResponse]
$creadListPrec :: ReadPrec [GetMergeConflictsResponse]
readPrec :: ReadPrec GetMergeConflictsResponse
$creadPrec :: ReadPrec GetMergeConflictsResponse
readList :: ReadS [GetMergeConflictsResponse]
$creadList :: ReadS [GetMergeConflictsResponse]
readsPrec :: Int -> ReadS GetMergeConflictsResponse
$creadsPrec :: Int -> ReadS GetMergeConflictsResponse
Prelude.Read, Int -> GetMergeConflictsResponse -> ShowS
[GetMergeConflictsResponse] -> ShowS
GetMergeConflictsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMergeConflictsResponse] -> ShowS
$cshowList :: [GetMergeConflictsResponse] -> ShowS
show :: GetMergeConflictsResponse -> String
$cshow :: GetMergeConflictsResponse -> String
showsPrec :: Int -> GetMergeConflictsResponse -> ShowS
$cshowsPrec :: Int -> GetMergeConflictsResponse -> ShowS
Prelude.Show, forall x.
Rep GetMergeConflictsResponse x -> GetMergeConflictsResponse
forall x.
GetMergeConflictsResponse -> Rep GetMergeConflictsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMergeConflictsResponse x -> GetMergeConflictsResponse
$cfrom :: forall x.
GetMergeConflictsResponse -> Rep GetMergeConflictsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMergeConflictsResponse' 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', 'getMergeConflictsResponse_baseCommitId' - The commit ID of the merge base.
--
-- 'nextToken', 'getMergeConflictsResponse_nextToken' - An enumeration token that can be used in a request to return the next
-- batch of the results.
--
-- 'httpStatus', 'getMergeConflictsResponse_httpStatus' - The response's http status code.
--
-- 'mergeable', 'getMergeConflictsResponse_mergeable' - A Boolean value that indicates whether the code is mergeable by the
-- specified merge option.
--
-- 'destinationCommitId', 'getMergeConflictsResponse_destinationCommitId' - The commit ID of the destination commit specifier that was used in the
-- merge evaluation.
--
-- 'sourceCommitId', 'getMergeConflictsResponse_sourceCommitId' - The commit ID of the source commit specifier that was used in the merge
-- evaluation.
--
-- 'conflictMetadataList', 'getMergeConflictsResponse_conflictMetadataList' - A list of metadata for any conflicting files. If the specified merge
-- strategy is FAST_FORWARD_MERGE, this list is always empty.
newGetMergeConflictsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'mergeable'
  Prelude.Bool ->
  -- | 'destinationCommitId'
  Prelude.Text ->
  -- | 'sourceCommitId'
  Prelude.Text ->
  GetMergeConflictsResponse
newGetMergeConflictsResponse :: Int -> Bool -> Text -> Text -> GetMergeConflictsResponse
newGetMergeConflictsResponse
  Int
pHttpStatus_
  Bool
pMergeable_
  Text
pDestinationCommitId_
  Text
pSourceCommitId_ =
    GetMergeConflictsResponse'
      { $sel:baseCommitId:GetMergeConflictsResponse' :: Maybe Text
baseCommitId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetMergeConflictsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetMergeConflictsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:mergeable:GetMergeConflictsResponse' :: Bool
mergeable = Bool
pMergeable_,
        $sel:destinationCommitId:GetMergeConflictsResponse' :: Text
destinationCommitId = Text
pDestinationCommitId_,
        $sel:sourceCommitId:GetMergeConflictsResponse' :: Text
sourceCommitId = Text
pSourceCommitId_,
        $sel:conflictMetadataList:GetMergeConflictsResponse' :: [ConflictMetadata]
conflictMetadataList = forall a. Monoid a => a
Prelude.mempty
      }

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

-- | An enumeration token that can be used in a request to return the next
-- batch of the results.
getMergeConflictsResponse_nextToken :: Lens.Lens' GetMergeConflictsResponse (Prelude.Maybe Prelude.Text)
getMergeConflictsResponse_nextToken :: Lens' GetMergeConflictsResponse (Maybe Text)
getMergeConflictsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeConflictsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetMergeConflictsResponse
s@GetMergeConflictsResponse' {} Maybe Text
a -> GetMergeConflictsResponse
s {$sel:nextToken:GetMergeConflictsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetMergeConflictsResponse)

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

-- | A Boolean value that indicates whether the code is mergeable by the
-- specified merge option.
getMergeConflictsResponse_mergeable :: Lens.Lens' GetMergeConflictsResponse Prelude.Bool
getMergeConflictsResponse_mergeable :: Lens' GetMergeConflictsResponse Bool
getMergeConflictsResponse_mergeable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeConflictsResponse' {Bool
mergeable :: Bool
$sel:mergeable:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> Bool
mergeable} -> Bool
mergeable) (\s :: GetMergeConflictsResponse
s@GetMergeConflictsResponse' {} Bool
a -> GetMergeConflictsResponse
s {$sel:mergeable:GetMergeConflictsResponse' :: Bool
mergeable = Bool
a} :: GetMergeConflictsResponse)

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

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

-- | A list of metadata for any conflicting files. If the specified merge
-- strategy is FAST_FORWARD_MERGE, this list is always empty.
getMergeConflictsResponse_conflictMetadataList :: Lens.Lens' GetMergeConflictsResponse [ConflictMetadata]
getMergeConflictsResponse_conflictMetadataList :: Lens' GetMergeConflictsResponse [ConflictMetadata]
getMergeConflictsResponse_conflictMetadataList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMergeConflictsResponse' {[ConflictMetadata]
conflictMetadataList :: [ConflictMetadata]
$sel:conflictMetadataList:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> [ConflictMetadata]
conflictMetadataList} -> [ConflictMetadata]
conflictMetadataList) (\s :: GetMergeConflictsResponse
s@GetMergeConflictsResponse' {} [ConflictMetadata]
a -> GetMergeConflictsResponse
s {$sel:conflictMetadataList:GetMergeConflictsResponse' :: [ConflictMetadata]
conflictMetadataList = [ConflictMetadata]
a} :: GetMergeConflictsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.NFData GetMergeConflictsResponse where
  rnf :: GetMergeConflictsResponse -> ()
rnf GetMergeConflictsResponse' {Bool
Int
[ConflictMetadata]
Maybe Text
Text
conflictMetadataList :: [ConflictMetadata]
sourceCommitId :: Text
destinationCommitId :: Text
mergeable :: Bool
httpStatus :: Int
nextToken :: Maybe Text
baseCommitId :: Maybe Text
$sel:conflictMetadataList:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> [ConflictMetadata]
$sel:sourceCommitId:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> Text
$sel:destinationCommitId:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> Text
$sel:mergeable:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> Bool
$sel:httpStatus:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> Int
$sel:nextToken:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> Maybe Text
$sel:baseCommitId:GetMergeConflictsResponse' :: GetMergeConflictsResponse -> 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
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Bool
mergeable
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
destinationCommitId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceCommitId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [ConflictMetadata]
conflictMetadataList