{-# 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.Amplify.StartDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts a deployment for a manually deployed app. Manually deployed apps
-- are not connected to a repository.
module Amazonka.Amplify.StartDeployment
  ( -- * Creating a Request
    StartDeployment (..),
    newStartDeployment,

    -- * Request Lenses
    startDeployment_jobId,
    startDeployment_sourceUrl,
    startDeployment_appId,
    startDeployment_branchName,

    -- * Destructuring the Response
    StartDeploymentResponse (..),
    newStartDeploymentResponse,

    -- * Response Lenses
    startDeploymentResponse_httpStatus,
    startDeploymentResponse_jobSummary,
  )
where

import Amazonka.Amplify.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

-- | The request structure for the start a deployment request.
--
-- /See:/ 'newStartDeployment' smart constructor.
data StartDeployment = StartDeployment'
  { -- | The job ID for this deployment, generated by the create deployment
    -- request.
    StartDeployment -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The source URL for this deployment, used when calling start deployment
    -- without create deployment. The source URL can be any HTTP GET URL that
    -- is publicly accessible and downloads a single .zip file.
    StartDeployment -> Maybe Text
sourceUrl :: Prelude.Maybe Prelude.Text,
    -- | The unique ID for an Amplify app.
    StartDeployment -> Text
appId :: Prelude.Text,
    -- | The name for the branch, for the job.
    StartDeployment -> Text
branchName :: Prelude.Text
  }
  deriving (StartDeployment -> StartDeployment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartDeployment -> StartDeployment -> Bool
$c/= :: StartDeployment -> StartDeployment -> Bool
== :: StartDeployment -> StartDeployment -> Bool
$c== :: StartDeployment -> StartDeployment -> Bool
Prelude.Eq, ReadPrec [StartDeployment]
ReadPrec StartDeployment
Int -> ReadS StartDeployment
ReadS [StartDeployment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartDeployment]
$creadListPrec :: ReadPrec [StartDeployment]
readPrec :: ReadPrec StartDeployment
$creadPrec :: ReadPrec StartDeployment
readList :: ReadS [StartDeployment]
$creadList :: ReadS [StartDeployment]
readsPrec :: Int -> ReadS StartDeployment
$creadsPrec :: Int -> ReadS StartDeployment
Prelude.Read, Int -> StartDeployment -> ShowS
[StartDeployment] -> ShowS
StartDeployment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartDeployment] -> ShowS
$cshowList :: [StartDeployment] -> ShowS
show :: StartDeployment -> String
$cshow :: StartDeployment -> String
showsPrec :: Int -> StartDeployment -> ShowS
$cshowsPrec :: Int -> StartDeployment -> ShowS
Prelude.Show, forall x. Rep StartDeployment x -> StartDeployment
forall x. StartDeployment -> Rep StartDeployment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartDeployment x -> StartDeployment
$cfrom :: forall x. StartDeployment -> Rep StartDeployment x
Prelude.Generic)

-- |
-- Create a value of 'StartDeployment' 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:
--
-- 'jobId', 'startDeployment_jobId' - The job ID for this deployment, generated by the create deployment
-- request.
--
-- 'sourceUrl', 'startDeployment_sourceUrl' - The source URL for this deployment, used when calling start deployment
-- without create deployment. The source URL can be any HTTP GET URL that
-- is publicly accessible and downloads a single .zip file.
--
-- 'appId', 'startDeployment_appId' - The unique ID for an Amplify app.
--
-- 'branchName', 'startDeployment_branchName' - The name for the branch, for the job.
newStartDeployment ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'branchName'
  Prelude.Text ->
  StartDeployment
newStartDeployment :: Text -> Text -> StartDeployment
newStartDeployment Text
pAppId_ Text
pBranchName_ =
  StartDeployment'
    { $sel:jobId:StartDeployment' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceUrl:StartDeployment' :: Maybe Text
sourceUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:appId:StartDeployment' :: Text
appId = Text
pAppId_,
      $sel:branchName:StartDeployment' :: Text
branchName = Text
pBranchName_
    }

-- | The job ID for this deployment, generated by the create deployment
-- request.
startDeployment_jobId :: Lens.Lens' StartDeployment (Prelude.Maybe Prelude.Text)
startDeployment_jobId :: Lens' StartDeployment (Maybe Text)
startDeployment_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Maybe Text
jobId :: Maybe Text
$sel:jobId:StartDeployment' :: StartDeployment -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: StartDeployment
s@StartDeployment' {} Maybe Text
a -> StartDeployment
s {$sel:jobId:StartDeployment' :: Maybe Text
jobId = Maybe Text
a} :: StartDeployment)

-- | The source URL for this deployment, used when calling start deployment
-- without create deployment. The source URL can be any HTTP GET URL that
-- is publicly accessible and downloads a single .zip file.
startDeployment_sourceUrl :: Lens.Lens' StartDeployment (Prelude.Maybe Prelude.Text)
startDeployment_sourceUrl :: Lens' StartDeployment (Maybe Text)
startDeployment_sourceUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Maybe Text
sourceUrl :: Maybe Text
$sel:sourceUrl:StartDeployment' :: StartDeployment -> Maybe Text
sourceUrl} -> Maybe Text
sourceUrl) (\s :: StartDeployment
s@StartDeployment' {} Maybe Text
a -> StartDeployment
s {$sel:sourceUrl:StartDeployment' :: Maybe Text
sourceUrl = Maybe Text
a} :: StartDeployment)

-- | The unique ID for an Amplify app.
startDeployment_appId :: Lens.Lens' StartDeployment Prelude.Text
startDeployment_appId :: Lens' StartDeployment Text
startDeployment_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Text
appId :: Text
$sel:appId:StartDeployment' :: StartDeployment -> Text
appId} -> Text
appId) (\s :: StartDeployment
s@StartDeployment' {} Text
a -> StartDeployment
s {$sel:appId:StartDeployment' :: Text
appId = Text
a} :: StartDeployment)

-- | The name for the branch, for the job.
startDeployment_branchName :: Lens.Lens' StartDeployment Prelude.Text
startDeployment_branchName :: Lens' StartDeployment Text
startDeployment_branchName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Text
branchName :: Text
$sel:branchName:StartDeployment' :: StartDeployment -> Text
branchName} -> Text
branchName) (\s :: StartDeployment
s@StartDeployment' {} Text
a -> StartDeployment
s {$sel:branchName:StartDeployment' :: Text
branchName = Text
a} :: StartDeployment)

instance Core.AWSRequest StartDeployment where
  type
    AWSResponse StartDeployment =
      StartDeploymentResponse
  request :: (Service -> Service) -> StartDeployment -> Request StartDeployment
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 StartDeployment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartDeployment)))
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 ->
          Int -> JobSummary -> StartDeploymentResponse
StartDeploymentResponse'
            forall (f :: * -> *) a b. Functor 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
"jobSummary")
      )

instance Prelude.Hashable StartDeployment where
  hashWithSalt :: Int -> StartDeployment -> Int
hashWithSalt Int
_salt StartDeployment' {Maybe Text
Text
branchName :: Text
appId :: Text
sourceUrl :: Maybe Text
jobId :: Maybe Text
$sel:branchName:StartDeployment' :: StartDeployment -> Text
$sel:appId:StartDeployment' :: StartDeployment -> Text
$sel:sourceUrl:StartDeployment' :: StartDeployment -> Maybe Text
$sel:jobId:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
branchName

instance Prelude.NFData StartDeployment where
  rnf :: StartDeployment -> ()
rnf StartDeployment' {Maybe Text
Text
branchName :: Text
appId :: Text
sourceUrl :: Maybe Text
jobId :: Maybe Text
$sel:branchName:StartDeployment' :: StartDeployment -> Text
$sel:appId:StartDeployment' :: StartDeployment -> Text
$sel:sourceUrl:StartDeployment' :: StartDeployment -> Maybe Text
$sel:jobId:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
branchName

instance Data.ToHeaders StartDeployment where
  toHeaders :: StartDeployment -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StartDeployment where
  toJSON :: StartDeployment -> Value
toJSON StartDeployment' {Maybe Text
Text
branchName :: Text
appId :: Text
sourceUrl :: Maybe Text
jobId :: Maybe Text
$sel:branchName:StartDeployment' :: StartDeployment -> Text
$sel:appId:StartDeployment' :: StartDeployment -> Text
$sel:sourceUrl:StartDeployment' :: StartDeployment -> Maybe Text
$sel:jobId:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"jobId" 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
jobId,
            (Key
"sourceUrl" 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
sourceUrl
          ]
      )

instance Data.ToPath StartDeployment where
  toPath :: StartDeployment -> ByteString
toPath StartDeployment' {Maybe Text
Text
branchName :: Text
appId :: Text
sourceUrl :: Maybe Text
jobId :: Maybe Text
$sel:branchName:StartDeployment' :: StartDeployment -> Text
$sel:appId:StartDeployment' :: StartDeployment -> Text
$sel:sourceUrl:StartDeployment' :: StartDeployment -> Maybe Text
$sel:jobId:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId,
        ByteString
"/branches/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
branchName,
        ByteString
"/deployments/start"
      ]

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

-- | The result structure for the start a deployment request.
--
-- /See:/ 'newStartDeploymentResponse' smart constructor.
data StartDeploymentResponse = StartDeploymentResponse'
  { -- | The response's http status code.
    StartDeploymentResponse -> Int
httpStatus :: Prelude.Int,
    -- | The summary for the job.
    StartDeploymentResponse -> JobSummary
jobSummary :: JobSummary
  }
  deriving (StartDeploymentResponse -> StartDeploymentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
$c/= :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
== :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
$c== :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
Prelude.Eq, ReadPrec [StartDeploymentResponse]
ReadPrec StartDeploymentResponse
Int -> ReadS StartDeploymentResponse
ReadS [StartDeploymentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartDeploymentResponse]
$creadListPrec :: ReadPrec [StartDeploymentResponse]
readPrec :: ReadPrec StartDeploymentResponse
$creadPrec :: ReadPrec StartDeploymentResponse
readList :: ReadS [StartDeploymentResponse]
$creadList :: ReadS [StartDeploymentResponse]
readsPrec :: Int -> ReadS StartDeploymentResponse
$creadsPrec :: Int -> ReadS StartDeploymentResponse
Prelude.Read, Int -> StartDeploymentResponse -> ShowS
[StartDeploymentResponse] -> ShowS
StartDeploymentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartDeploymentResponse] -> ShowS
$cshowList :: [StartDeploymentResponse] -> ShowS
show :: StartDeploymentResponse -> String
$cshow :: StartDeploymentResponse -> String
showsPrec :: Int -> StartDeploymentResponse -> ShowS
$cshowsPrec :: Int -> StartDeploymentResponse -> ShowS
Prelude.Show, forall x. Rep StartDeploymentResponse x -> StartDeploymentResponse
forall x. StartDeploymentResponse -> Rep StartDeploymentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartDeploymentResponse x -> StartDeploymentResponse
$cfrom :: forall x. StartDeploymentResponse -> Rep StartDeploymentResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartDeploymentResponse' 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:
--
-- 'httpStatus', 'startDeploymentResponse_httpStatus' - The response's http status code.
--
-- 'jobSummary', 'startDeploymentResponse_jobSummary' - The summary for the job.
newStartDeploymentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'jobSummary'
  JobSummary ->
  StartDeploymentResponse
newStartDeploymentResponse :: Int -> JobSummary -> StartDeploymentResponse
newStartDeploymentResponse Int
pHttpStatus_ JobSummary
pJobSummary_ =
  StartDeploymentResponse'
    { $sel:httpStatus:StartDeploymentResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:jobSummary:StartDeploymentResponse' :: JobSummary
jobSummary = JobSummary
pJobSummary_
    }

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

-- | The summary for the job.
startDeploymentResponse_jobSummary :: Lens.Lens' StartDeploymentResponse JobSummary
startDeploymentResponse_jobSummary :: Lens' StartDeploymentResponse JobSummary
startDeploymentResponse_jobSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeploymentResponse' {JobSummary
jobSummary :: JobSummary
$sel:jobSummary:StartDeploymentResponse' :: StartDeploymentResponse -> JobSummary
jobSummary} -> JobSummary
jobSummary) (\s :: StartDeploymentResponse
s@StartDeploymentResponse' {} JobSummary
a -> StartDeploymentResponse
s {$sel:jobSummary:StartDeploymentResponse' :: JobSummary
jobSummary = JobSummary
a} :: StartDeploymentResponse)

instance Prelude.NFData StartDeploymentResponse where
  rnf :: StartDeploymentResponse -> ()
rnf StartDeploymentResponse' {Int
JobSummary
jobSummary :: JobSummary
httpStatus :: Int
$sel:jobSummary:StartDeploymentResponse' :: StartDeploymentResponse -> JobSummary
$sel:httpStatus:StartDeploymentResponse' :: StartDeploymentResponse -> Int
..} =
    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 JobSummary
jobSummary