{-# 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.AppConfig.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.
module Amazonka.AppConfig.StartDeployment
  ( -- * Creating a Request
    StartDeployment (..),
    newStartDeployment,

    -- * Request Lenses
    startDeployment_description,
    startDeployment_tags,
    startDeployment_applicationId,
    startDeployment_environmentId,
    startDeployment_deploymentStrategyId,
    startDeployment_configurationProfileId,
    startDeployment_configurationVersion,

    -- * Destructuring the Response
    Deployment (..),
    newDeployment,

    -- * Response Lenses
    deployment_applicationId,
    deployment_appliedExtensions,
    deployment_completedAt,
    deployment_configurationLocationUri,
    deployment_configurationName,
    deployment_configurationProfileId,
    deployment_configurationVersion,
    deployment_deploymentDurationInMinutes,
    deployment_deploymentNumber,
    deployment_deploymentStrategyId,
    deployment_description,
    deployment_environmentId,
    deployment_eventLog,
    deployment_finalBakeTimeInMinutes,
    deployment_growthFactor,
    deployment_growthType,
    deployment_percentageComplete,
    deployment_startedAt,
    deployment_state,
  )
where

import Amazonka.AppConfig.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:/ 'newStartDeployment' smart constructor.
data StartDeployment = StartDeployment'
  { -- | A description of the deployment.
    StartDeployment -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Metadata to assign to the deployment. Tags help organize and categorize
    -- your AppConfig resources. Each tag consists of a key and an optional
    -- value, both of which you define.
    StartDeployment -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The application ID.
    StartDeployment -> Text
applicationId :: Prelude.Text,
    -- | The environment ID.
    StartDeployment -> Text
environmentId :: Prelude.Text,
    -- | The deployment strategy ID.
    StartDeployment -> Text
deploymentStrategyId :: Prelude.Text,
    -- | The configuration profile ID.
    StartDeployment -> Text
configurationProfileId :: Prelude.Text,
    -- | The configuration version to deploy.
    StartDeployment -> Text
configurationVersion :: 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:
--
-- 'description', 'startDeployment_description' - A description of the deployment.
--
-- 'tags', 'startDeployment_tags' - Metadata to assign to the deployment. Tags help organize and categorize
-- your AppConfig resources. Each tag consists of a key and an optional
-- value, both of which you define.
--
-- 'applicationId', 'startDeployment_applicationId' - The application ID.
--
-- 'environmentId', 'startDeployment_environmentId' - The environment ID.
--
-- 'deploymentStrategyId', 'startDeployment_deploymentStrategyId' - The deployment strategy ID.
--
-- 'configurationProfileId', 'startDeployment_configurationProfileId' - The configuration profile ID.
--
-- 'configurationVersion', 'startDeployment_configurationVersion' - The configuration version to deploy.
newStartDeployment ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'environmentId'
  Prelude.Text ->
  -- | 'deploymentStrategyId'
  Prelude.Text ->
  -- | 'configurationProfileId'
  Prelude.Text ->
  -- | 'configurationVersion'
  Prelude.Text ->
  StartDeployment
newStartDeployment :: Text -> Text -> Text -> Text -> Text -> StartDeployment
newStartDeployment
  Text
pApplicationId_
  Text
pEnvironmentId_
  Text
pDeploymentStrategyId_
  Text
pConfigurationProfileId_
  Text
pConfigurationVersion_ =
    StartDeployment'
      { $sel:description:StartDeployment' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:StartDeployment' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:applicationId:StartDeployment' :: Text
applicationId = Text
pApplicationId_,
        $sel:environmentId:StartDeployment' :: Text
environmentId = Text
pEnvironmentId_,
        $sel:deploymentStrategyId:StartDeployment' :: Text
deploymentStrategyId = Text
pDeploymentStrategyId_,
        $sel:configurationProfileId:StartDeployment' :: Text
configurationProfileId = Text
pConfigurationProfileId_,
        $sel:configurationVersion:StartDeployment' :: Text
configurationVersion = Text
pConfigurationVersion_
      }

-- | A description of the deployment.
startDeployment_description :: Lens.Lens' StartDeployment (Prelude.Maybe Prelude.Text)
startDeployment_description :: Lens' StartDeployment (Maybe Text)
startDeployment_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Maybe Text
description :: Maybe Text
$sel:description:StartDeployment' :: StartDeployment -> Maybe Text
description} -> Maybe Text
description) (\s :: StartDeployment
s@StartDeployment' {} Maybe Text
a -> StartDeployment
s {$sel:description:StartDeployment' :: Maybe Text
description = Maybe Text
a} :: StartDeployment)

-- | Metadata to assign to the deployment. Tags help organize and categorize
-- your AppConfig resources. Each tag consists of a key and an optional
-- value, both of which you define.
startDeployment_tags :: Lens.Lens' StartDeployment (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startDeployment_tags :: Lens' StartDeployment (Maybe (HashMap Text Text))
startDeployment_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:StartDeployment' :: StartDeployment -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: StartDeployment
s@StartDeployment' {} Maybe (HashMap Text Text)
a -> StartDeployment
s {$sel:tags:StartDeployment' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: StartDeployment) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The application ID.
startDeployment_applicationId :: Lens.Lens' StartDeployment Prelude.Text
startDeployment_applicationId :: Lens' StartDeployment Text
startDeployment_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Text
applicationId :: Text
$sel:applicationId:StartDeployment' :: StartDeployment -> Text
applicationId} -> Text
applicationId) (\s :: StartDeployment
s@StartDeployment' {} Text
a -> StartDeployment
s {$sel:applicationId:StartDeployment' :: Text
applicationId = Text
a} :: StartDeployment)

-- | The environment ID.
startDeployment_environmentId :: Lens.Lens' StartDeployment Prelude.Text
startDeployment_environmentId :: Lens' StartDeployment Text
startDeployment_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Text
environmentId :: Text
$sel:environmentId:StartDeployment' :: StartDeployment -> Text
environmentId} -> Text
environmentId) (\s :: StartDeployment
s@StartDeployment' {} Text
a -> StartDeployment
s {$sel:environmentId:StartDeployment' :: Text
environmentId = Text
a} :: StartDeployment)

-- | The deployment strategy ID.
startDeployment_deploymentStrategyId :: Lens.Lens' StartDeployment Prelude.Text
startDeployment_deploymentStrategyId :: Lens' StartDeployment Text
startDeployment_deploymentStrategyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Text
deploymentStrategyId :: Text
$sel:deploymentStrategyId:StartDeployment' :: StartDeployment -> Text
deploymentStrategyId} -> Text
deploymentStrategyId) (\s :: StartDeployment
s@StartDeployment' {} Text
a -> StartDeployment
s {$sel:deploymentStrategyId:StartDeployment' :: Text
deploymentStrategyId = Text
a} :: StartDeployment)

-- | The configuration profile ID.
startDeployment_configurationProfileId :: Lens.Lens' StartDeployment Prelude.Text
startDeployment_configurationProfileId :: Lens' StartDeployment Text
startDeployment_configurationProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Text
configurationProfileId :: Text
$sel:configurationProfileId:StartDeployment' :: StartDeployment -> Text
configurationProfileId} -> Text
configurationProfileId) (\s :: StartDeployment
s@StartDeployment' {} Text
a -> StartDeployment
s {$sel:configurationProfileId:StartDeployment' :: Text
configurationProfileId = Text
a} :: StartDeployment)

-- | The configuration version to deploy.
startDeployment_configurationVersion :: Lens.Lens' StartDeployment Prelude.Text
startDeployment_configurationVersion :: Lens' StartDeployment Text
startDeployment_configurationVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDeployment' {Text
configurationVersion :: Text
$sel:configurationVersion:StartDeployment' :: StartDeployment -> Text
configurationVersion} -> Text
configurationVersion) (\s :: StartDeployment
s@StartDeployment' {} Text
a -> StartDeployment
s {$sel:configurationVersion:StartDeployment' :: Text
configurationVersion = Text
a} :: StartDeployment)

instance Core.AWSRequest StartDeployment where
  type AWSResponse StartDeployment = Deployment
  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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable StartDeployment where
  hashWithSalt :: Int -> StartDeployment -> Int
hashWithSalt Int
_salt StartDeployment' {Maybe Text
Maybe (HashMap Text Text)
Text
configurationVersion :: Text
configurationProfileId :: Text
deploymentStrategyId :: Text
environmentId :: Text
applicationId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:configurationVersion:StartDeployment' :: StartDeployment -> Text
$sel:configurationProfileId:StartDeployment' :: StartDeployment -> Text
$sel:deploymentStrategyId:StartDeployment' :: StartDeployment -> Text
$sel:environmentId:StartDeployment' :: StartDeployment -> Text
$sel:applicationId:StartDeployment' :: StartDeployment -> Text
$sel:tags:StartDeployment' :: StartDeployment -> Maybe (HashMap Text Text)
$sel:description:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deploymentStrategyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationProfileId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationVersion

instance Prelude.NFData StartDeployment where
  rnf :: StartDeployment -> ()
rnf StartDeployment' {Maybe Text
Maybe (HashMap Text Text)
Text
configurationVersion :: Text
configurationProfileId :: Text
deploymentStrategyId :: Text
environmentId :: Text
applicationId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:configurationVersion:StartDeployment' :: StartDeployment -> Text
$sel:configurationProfileId:StartDeployment' :: StartDeployment -> Text
$sel:deploymentStrategyId:StartDeployment' :: StartDeployment -> Text
$sel:environmentId:StartDeployment' :: StartDeployment -> Text
$sel:applicationId:StartDeployment' :: StartDeployment -> Text
$sel:tags:StartDeployment' :: StartDeployment -> Maybe (HashMap Text Text)
$sel:description:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
deploymentStrategyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configurationProfileId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configurationVersion

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
Maybe (HashMap Text Text)
Text
configurationVersion :: Text
configurationProfileId :: Text
deploymentStrategyId :: Text
environmentId :: Text
applicationId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:configurationVersion:StartDeployment' :: StartDeployment -> Text
$sel:configurationProfileId:StartDeployment' :: StartDeployment -> Text
$sel:deploymentStrategyId:StartDeployment' :: StartDeployment -> Text
$sel:environmentId:StartDeployment' :: StartDeployment -> Text
$sel:applicationId:StartDeployment' :: StartDeployment -> Text
$sel:tags:StartDeployment' :: StartDeployment -> Maybe (HashMap Text Text)
$sel:description:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (Key
"Tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"DeploymentStrategyId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
deploymentStrategyId
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"ConfigurationProfileId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
configurationProfileId
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"ConfigurationVersion"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
configurationVersion
              )
          ]
      )

instance Data.ToPath StartDeployment where
  toPath :: StartDeployment -> ByteString
toPath StartDeployment' {Maybe Text
Maybe (HashMap Text Text)
Text
configurationVersion :: Text
configurationProfileId :: Text
deploymentStrategyId :: Text
environmentId :: Text
applicationId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:configurationVersion:StartDeployment' :: StartDeployment -> Text
$sel:configurationProfileId:StartDeployment' :: StartDeployment -> Text
$sel:deploymentStrategyId:StartDeployment' :: StartDeployment -> Text
$sel:environmentId:StartDeployment' :: StartDeployment -> Text
$sel:applicationId:StartDeployment' :: StartDeployment -> Text
$sel:tags:StartDeployment' :: StartDeployment -> Maybe (HashMap Text Text)
$sel:description:StartDeployment' :: StartDeployment -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/environments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentId,
        ByteString
"/deployments"
      ]

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