{-# 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.Glue.UpdateSourceControlFromJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Synchronizes a job to the source control repository. This operation
-- takes the job artifacts from the Glue internal stores and makes a commit
-- to the remote repository that is configured on the job.
--
-- This API supports optional parameters which take in the repository
-- information.
module Amazonka.Glue.UpdateSourceControlFromJob
  ( -- * Creating a Request
    UpdateSourceControlFromJob (..),
    newUpdateSourceControlFromJob,

    -- * Request Lenses
    updateSourceControlFromJob_authStrategy,
    updateSourceControlFromJob_authToken,
    updateSourceControlFromJob_branchName,
    updateSourceControlFromJob_commitId,
    updateSourceControlFromJob_folder,
    updateSourceControlFromJob_jobName,
    updateSourceControlFromJob_provider,
    updateSourceControlFromJob_repositoryName,
    updateSourceControlFromJob_repositoryOwner,

    -- * Destructuring the Response
    UpdateSourceControlFromJobResponse (..),
    newUpdateSourceControlFromJobResponse,

    -- * Response Lenses
    updateSourceControlFromJobResponse_jobName,
    updateSourceControlFromJobResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateSourceControlFromJob' smart constructor.
data UpdateSourceControlFromJob = UpdateSourceControlFromJob'
  { -- | The type of authentication, which can be an authentication token stored
    -- in Amazon Web Services Secrets Manager, or a personal access token.
    UpdateSourceControlFromJob -> Maybe SourceControlAuthStrategy
authStrategy :: Prelude.Maybe SourceControlAuthStrategy,
    -- | The value of the authorization token.
    UpdateSourceControlFromJob -> Maybe Text
authToken :: Prelude.Maybe Prelude.Text,
    -- | An optional branch in the remote repository.
    UpdateSourceControlFromJob -> Maybe Text
branchName :: Prelude.Maybe Prelude.Text,
    -- | A commit ID for a commit in the remote repository.
    UpdateSourceControlFromJob -> Maybe Text
commitId :: Prelude.Maybe Prelude.Text,
    -- | An optional folder in the remote repository.
    UpdateSourceControlFromJob -> Maybe Text
folder :: Prelude.Maybe Prelude.Text,
    -- | The name of the Glue job to be synchronized to or from the remote
    -- repository.
    UpdateSourceControlFromJob -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    -- | The provider for the remote repository.
    UpdateSourceControlFromJob -> Maybe SourceControlProvider
provider :: Prelude.Maybe SourceControlProvider,
    -- | The name of the remote repository that contains the job artifacts.
    UpdateSourceControlFromJob -> Maybe Text
repositoryName :: Prelude.Maybe Prelude.Text,
    -- | The owner of the remote repository that contains the job artifacts.
    UpdateSourceControlFromJob -> Maybe Text
repositoryOwner :: Prelude.Maybe Prelude.Text
  }
  deriving (UpdateSourceControlFromJob -> UpdateSourceControlFromJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSourceControlFromJob -> UpdateSourceControlFromJob -> Bool
$c/= :: UpdateSourceControlFromJob -> UpdateSourceControlFromJob -> Bool
== :: UpdateSourceControlFromJob -> UpdateSourceControlFromJob -> Bool
$c== :: UpdateSourceControlFromJob -> UpdateSourceControlFromJob -> Bool
Prelude.Eq, ReadPrec [UpdateSourceControlFromJob]
ReadPrec UpdateSourceControlFromJob
Int -> ReadS UpdateSourceControlFromJob
ReadS [UpdateSourceControlFromJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSourceControlFromJob]
$creadListPrec :: ReadPrec [UpdateSourceControlFromJob]
readPrec :: ReadPrec UpdateSourceControlFromJob
$creadPrec :: ReadPrec UpdateSourceControlFromJob
readList :: ReadS [UpdateSourceControlFromJob]
$creadList :: ReadS [UpdateSourceControlFromJob]
readsPrec :: Int -> ReadS UpdateSourceControlFromJob
$creadsPrec :: Int -> ReadS UpdateSourceControlFromJob
Prelude.Read, Int -> UpdateSourceControlFromJob -> ShowS
[UpdateSourceControlFromJob] -> ShowS
UpdateSourceControlFromJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSourceControlFromJob] -> ShowS
$cshowList :: [UpdateSourceControlFromJob] -> ShowS
show :: UpdateSourceControlFromJob -> String
$cshow :: UpdateSourceControlFromJob -> String
showsPrec :: Int -> UpdateSourceControlFromJob -> ShowS
$cshowsPrec :: Int -> UpdateSourceControlFromJob -> ShowS
Prelude.Show, forall x.
Rep UpdateSourceControlFromJob x -> UpdateSourceControlFromJob
forall x.
UpdateSourceControlFromJob -> Rep UpdateSourceControlFromJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSourceControlFromJob x -> UpdateSourceControlFromJob
$cfrom :: forall x.
UpdateSourceControlFromJob -> Rep UpdateSourceControlFromJob x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSourceControlFromJob' 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:
--
-- 'authStrategy', 'updateSourceControlFromJob_authStrategy' - The type of authentication, which can be an authentication token stored
-- in Amazon Web Services Secrets Manager, or a personal access token.
--
-- 'authToken', 'updateSourceControlFromJob_authToken' - The value of the authorization token.
--
-- 'branchName', 'updateSourceControlFromJob_branchName' - An optional branch in the remote repository.
--
-- 'commitId', 'updateSourceControlFromJob_commitId' - A commit ID for a commit in the remote repository.
--
-- 'folder', 'updateSourceControlFromJob_folder' - An optional folder in the remote repository.
--
-- 'jobName', 'updateSourceControlFromJob_jobName' - The name of the Glue job to be synchronized to or from the remote
-- repository.
--
-- 'provider', 'updateSourceControlFromJob_provider' - The provider for the remote repository.
--
-- 'repositoryName', 'updateSourceControlFromJob_repositoryName' - The name of the remote repository that contains the job artifacts.
--
-- 'repositoryOwner', 'updateSourceControlFromJob_repositoryOwner' - The owner of the remote repository that contains the job artifacts.
newUpdateSourceControlFromJob ::
  UpdateSourceControlFromJob
newUpdateSourceControlFromJob :: UpdateSourceControlFromJob
newUpdateSourceControlFromJob =
  UpdateSourceControlFromJob'
    { $sel:authStrategy:UpdateSourceControlFromJob' :: Maybe SourceControlAuthStrategy
authStrategy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authToken:UpdateSourceControlFromJob' :: Maybe Text
authToken = forall a. Maybe a
Prelude.Nothing,
      $sel:branchName:UpdateSourceControlFromJob' :: Maybe Text
branchName = forall a. Maybe a
Prelude.Nothing,
      $sel:commitId:UpdateSourceControlFromJob' :: Maybe Text
commitId = forall a. Maybe a
Prelude.Nothing,
      $sel:folder:UpdateSourceControlFromJob' :: Maybe Text
folder = forall a. Maybe a
Prelude.Nothing,
      $sel:jobName:UpdateSourceControlFromJob' :: Maybe Text
jobName = forall a. Maybe a
Prelude.Nothing,
      $sel:provider:UpdateSourceControlFromJob' :: Maybe SourceControlProvider
provider = forall a. Maybe a
Prelude.Nothing,
      $sel:repositoryName:UpdateSourceControlFromJob' :: Maybe Text
repositoryName = forall a. Maybe a
Prelude.Nothing,
      $sel:repositoryOwner:UpdateSourceControlFromJob' :: Maybe Text
repositoryOwner = forall a. Maybe a
Prelude.Nothing
    }

-- | The type of authentication, which can be an authentication token stored
-- in Amazon Web Services Secrets Manager, or a personal access token.
updateSourceControlFromJob_authStrategy :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe SourceControlAuthStrategy)
updateSourceControlFromJob_authStrategy :: Lens' UpdateSourceControlFromJob (Maybe SourceControlAuthStrategy)
updateSourceControlFromJob_authStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe SourceControlAuthStrategy
authStrategy :: Maybe SourceControlAuthStrategy
$sel:authStrategy:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlAuthStrategy
authStrategy} -> Maybe SourceControlAuthStrategy
authStrategy) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe SourceControlAuthStrategy
a -> UpdateSourceControlFromJob
s {$sel:authStrategy:UpdateSourceControlFromJob' :: Maybe SourceControlAuthStrategy
authStrategy = Maybe SourceControlAuthStrategy
a} :: UpdateSourceControlFromJob)

-- | The value of the authorization token.
updateSourceControlFromJob_authToken :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe Prelude.Text)
updateSourceControlFromJob_authToken :: Lens' UpdateSourceControlFromJob (Maybe Text)
updateSourceControlFromJob_authToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe Text
authToken :: Maybe Text
$sel:authToken:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
authToken} -> Maybe Text
authToken) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe Text
a -> UpdateSourceControlFromJob
s {$sel:authToken:UpdateSourceControlFromJob' :: Maybe Text
authToken = Maybe Text
a} :: UpdateSourceControlFromJob)

-- | An optional branch in the remote repository.
updateSourceControlFromJob_branchName :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe Prelude.Text)
updateSourceControlFromJob_branchName :: Lens' UpdateSourceControlFromJob (Maybe Text)
updateSourceControlFromJob_branchName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe Text
branchName :: Maybe Text
$sel:branchName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
branchName} -> Maybe Text
branchName) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe Text
a -> UpdateSourceControlFromJob
s {$sel:branchName:UpdateSourceControlFromJob' :: Maybe Text
branchName = Maybe Text
a} :: UpdateSourceControlFromJob)

-- | A commit ID for a commit in the remote repository.
updateSourceControlFromJob_commitId :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe Prelude.Text)
updateSourceControlFromJob_commitId :: Lens' UpdateSourceControlFromJob (Maybe Text)
updateSourceControlFromJob_commitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe Text
commitId :: Maybe Text
$sel:commitId:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
commitId} -> Maybe Text
commitId) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe Text
a -> UpdateSourceControlFromJob
s {$sel:commitId:UpdateSourceControlFromJob' :: Maybe Text
commitId = Maybe Text
a} :: UpdateSourceControlFromJob)

-- | An optional folder in the remote repository.
updateSourceControlFromJob_folder :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe Prelude.Text)
updateSourceControlFromJob_folder :: Lens' UpdateSourceControlFromJob (Maybe Text)
updateSourceControlFromJob_folder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe Text
folder :: Maybe Text
$sel:folder:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
folder} -> Maybe Text
folder) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe Text
a -> UpdateSourceControlFromJob
s {$sel:folder:UpdateSourceControlFromJob' :: Maybe Text
folder = Maybe Text
a} :: UpdateSourceControlFromJob)

-- | The name of the Glue job to be synchronized to or from the remote
-- repository.
updateSourceControlFromJob_jobName :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe Prelude.Text)
updateSourceControlFromJob_jobName :: Lens' UpdateSourceControlFromJob (Maybe Text)
updateSourceControlFromJob_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe Text
jobName :: Maybe Text
$sel:jobName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
jobName} -> Maybe Text
jobName) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe Text
a -> UpdateSourceControlFromJob
s {$sel:jobName:UpdateSourceControlFromJob' :: Maybe Text
jobName = Maybe Text
a} :: UpdateSourceControlFromJob)

-- | The provider for the remote repository.
updateSourceControlFromJob_provider :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe SourceControlProvider)
updateSourceControlFromJob_provider :: Lens' UpdateSourceControlFromJob (Maybe SourceControlProvider)
updateSourceControlFromJob_provider = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe SourceControlProvider
provider :: Maybe SourceControlProvider
$sel:provider:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlProvider
provider} -> Maybe SourceControlProvider
provider) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe SourceControlProvider
a -> UpdateSourceControlFromJob
s {$sel:provider:UpdateSourceControlFromJob' :: Maybe SourceControlProvider
provider = Maybe SourceControlProvider
a} :: UpdateSourceControlFromJob)

-- | The name of the remote repository that contains the job artifacts.
updateSourceControlFromJob_repositoryName :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe Prelude.Text)
updateSourceControlFromJob_repositoryName :: Lens' UpdateSourceControlFromJob (Maybe Text)
updateSourceControlFromJob_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe Text
repositoryName :: Maybe Text
$sel:repositoryName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
repositoryName} -> Maybe Text
repositoryName) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe Text
a -> UpdateSourceControlFromJob
s {$sel:repositoryName:UpdateSourceControlFromJob' :: Maybe Text
repositoryName = Maybe Text
a} :: UpdateSourceControlFromJob)

-- | The owner of the remote repository that contains the job artifacts.
updateSourceControlFromJob_repositoryOwner :: Lens.Lens' UpdateSourceControlFromJob (Prelude.Maybe Prelude.Text)
updateSourceControlFromJob_repositoryOwner :: Lens' UpdateSourceControlFromJob (Maybe Text)
updateSourceControlFromJob_repositoryOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJob' {Maybe Text
repositoryOwner :: Maybe Text
$sel:repositoryOwner:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
repositoryOwner} -> Maybe Text
repositoryOwner) (\s :: UpdateSourceControlFromJob
s@UpdateSourceControlFromJob' {} Maybe Text
a -> UpdateSourceControlFromJob
s {$sel:repositoryOwner:UpdateSourceControlFromJob' :: Maybe Text
repositoryOwner = Maybe Text
a} :: UpdateSourceControlFromJob)

instance Core.AWSRequest UpdateSourceControlFromJob where
  type
    AWSResponse UpdateSourceControlFromJob =
      UpdateSourceControlFromJobResponse
  request :: (Service -> Service)
-> UpdateSourceControlFromJob -> Request UpdateSourceControlFromJob
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 UpdateSourceControlFromJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateSourceControlFromJob)))
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 -> Int -> UpdateSourceControlFromJobResponse
UpdateSourceControlFromJobResponse'
            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
"JobName")
            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 UpdateSourceControlFromJob where
  hashWithSalt :: Int -> UpdateSourceControlFromJob -> Int
hashWithSalt Int
_salt UpdateSourceControlFromJob' {Maybe Text
Maybe SourceControlAuthStrategy
Maybe SourceControlProvider
repositoryOwner :: Maybe Text
repositoryName :: Maybe Text
provider :: Maybe SourceControlProvider
jobName :: Maybe Text
folder :: Maybe Text
commitId :: Maybe Text
branchName :: Maybe Text
authToken :: Maybe Text
authStrategy :: Maybe SourceControlAuthStrategy
$sel:repositoryOwner:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:repositoryName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:provider:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlProvider
$sel:jobName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:folder:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:commitId:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:branchName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:authToken:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:authStrategy:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlAuthStrategy
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SourceControlAuthStrategy
authStrategy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
authToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
branchName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
commitId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
folder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SourceControlProvider
provider
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
repositoryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
repositoryOwner

instance Prelude.NFData UpdateSourceControlFromJob where
  rnf :: UpdateSourceControlFromJob -> ()
rnf UpdateSourceControlFromJob' {Maybe Text
Maybe SourceControlAuthStrategy
Maybe SourceControlProvider
repositoryOwner :: Maybe Text
repositoryName :: Maybe Text
provider :: Maybe SourceControlProvider
jobName :: Maybe Text
folder :: Maybe Text
commitId :: Maybe Text
branchName :: Maybe Text
authToken :: Maybe Text
authStrategy :: Maybe SourceControlAuthStrategy
$sel:repositoryOwner:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:repositoryName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:provider:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlProvider
$sel:jobName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:folder:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:commitId:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:branchName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:authToken:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:authStrategy:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlAuthStrategy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SourceControlAuthStrategy
authStrategy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
branchName
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
folder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SourceControlProvider
provider
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
repositoryName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
repositoryOwner

instance Data.ToHeaders UpdateSourceControlFromJob where
  toHeaders :: UpdateSourceControlFromJob -> 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
"AWSGlue.UpdateSourceControlFromJob" ::
                          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 UpdateSourceControlFromJob where
  toJSON :: UpdateSourceControlFromJob -> Value
toJSON UpdateSourceControlFromJob' {Maybe Text
Maybe SourceControlAuthStrategy
Maybe SourceControlProvider
repositoryOwner :: Maybe Text
repositoryName :: Maybe Text
provider :: Maybe SourceControlProvider
jobName :: Maybe Text
folder :: Maybe Text
commitId :: Maybe Text
branchName :: Maybe Text
authToken :: Maybe Text
authStrategy :: Maybe SourceControlAuthStrategy
$sel:repositoryOwner:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:repositoryName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:provider:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlProvider
$sel:jobName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:folder:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:commitId:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:branchName:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:authToken:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe Text
$sel:authStrategy:UpdateSourceControlFromJob' :: UpdateSourceControlFromJob -> Maybe SourceControlAuthStrategy
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AuthStrategy" 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 SourceControlAuthStrategy
authStrategy,
            (Key
"AuthToken" 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
authToken,
            (Key
"BranchName" 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
branchName,
            (Key
"CommitId" 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
commitId,
            (Key
"Folder" 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
folder,
            (Key
"JobName" 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
jobName,
            (Key
"Provider" 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 SourceControlProvider
provider,
            (Key
"RepositoryName" 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
repositoryName,
            (Key
"RepositoryOwner" 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
repositoryOwner
          ]
      )

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

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

-- | /See:/ 'newUpdateSourceControlFromJobResponse' smart constructor.
data UpdateSourceControlFromJobResponse = UpdateSourceControlFromJobResponse'
  { -- | The name of the Glue job.
    UpdateSourceControlFromJobResponse -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateSourceControlFromJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateSourceControlFromJobResponse
-> UpdateSourceControlFromJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSourceControlFromJobResponse
-> UpdateSourceControlFromJobResponse -> Bool
$c/= :: UpdateSourceControlFromJobResponse
-> UpdateSourceControlFromJobResponse -> Bool
== :: UpdateSourceControlFromJobResponse
-> UpdateSourceControlFromJobResponse -> Bool
$c== :: UpdateSourceControlFromJobResponse
-> UpdateSourceControlFromJobResponse -> Bool
Prelude.Eq, ReadPrec [UpdateSourceControlFromJobResponse]
ReadPrec UpdateSourceControlFromJobResponse
Int -> ReadS UpdateSourceControlFromJobResponse
ReadS [UpdateSourceControlFromJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSourceControlFromJobResponse]
$creadListPrec :: ReadPrec [UpdateSourceControlFromJobResponse]
readPrec :: ReadPrec UpdateSourceControlFromJobResponse
$creadPrec :: ReadPrec UpdateSourceControlFromJobResponse
readList :: ReadS [UpdateSourceControlFromJobResponse]
$creadList :: ReadS [UpdateSourceControlFromJobResponse]
readsPrec :: Int -> ReadS UpdateSourceControlFromJobResponse
$creadsPrec :: Int -> ReadS UpdateSourceControlFromJobResponse
Prelude.Read, Int -> UpdateSourceControlFromJobResponse -> ShowS
[UpdateSourceControlFromJobResponse] -> ShowS
UpdateSourceControlFromJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSourceControlFromJobResponse] -> ShowS
$cshowList :: [UpdateSourceControlFromJobResponse] -> ShowS
show :: UpdateSourceControlFromJobResponse -> String
$cshow :: UpdateSourceControlFromJobResponse -> String
showsPrec :: Int -> UpdateSourceControlFromJobResponse -> ShowS
$cshowsPrec :: Int -> UpdateSourceControlFromJobResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateSourceControlFromJobResponse x
-> UpdateSourceControlFromJobResponse
forall x.
UpdateSourceControlFromJobResponse
-> Rep UpdateSourceControlFromJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSourceControlFromJobResponse x
-> UpdateSourceControlFromJobResponse
$cfrom :: forall x.
UpdateSourceControlFromJobResponse
-> Rep UpdateSourceControlFromJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSourceControlFromJobResponse' 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:
--
-- 'jobName', 'updateSourceControlFromJobResponse_jobName' - The name of the Glue job.
--
-- 'httpStatus', 'updateSourceControlFromJobResponse_httpStatus' - The response's http status code.
newUpdateSourceControlFromJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateSourceControlFromJobResponse
newUpdateSourceControlFromJobResponse :: Int -> UpdateSourceControlFromJobResponse
newUpdateSourceControlFromJobResponse Int
pHttpStatus_ =
  UpdateSourceControlFromJobResponse'
    { $sel:jobName:UpdateSourceControlFromJobResponse' :: Maybe Text
jobName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateSourceControlFromJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the Glue job.
updateSourceControlFromJobResponse_jobName :: Lens.Lens' UpdateSourceControlFromJobResponse (Prelude.Maybe Prelude.Text)
updateSourceControlFromJobResponse_jobName :: Lens' UpdateSourceControlFromJobResponse (Maybe Text)
updateSourceControlFromJobResponse_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSourceControlFromJobResponse' {Maybe Text
jobName :: Maybe Text
$sel:jobName:UpdateSourceControlFromJobResponse' :: UpdateSourceControlFromJobResponse -> Maybe Text
jobName} -> Maybe Text
jobName) (\s :: UpdateSourceControlFromJobResponse
s@UpdateSourceControlFromJobResponse' {} Maybe Text
a -> UpdateSourceControlFromJobResponse
s {$sel:jobName:UpdateSourceControlFromJobResponse' :: Maybe Text
jobName = Maybe Text
a} :: UpdateSourceControlFromJobResponse)

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

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