{-# 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.CloudFront.CreateContinuousDeploymentPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a continuous deployment policy that distributes traffic for a
-- custom domain name to two different CloudFront distributions.
--
-- To use a continuous deployment policy, first use @CopyDistribution@ to
-- create a staging distribution, then use @UpdateDistribution@ to modify
-- the staging distribution\'s configuration.
--
-- After you create and update a staging distribution, you can use a
-- continuous deployment policy to incrementally move traffic to the
-- staging distribution. This workflow enables you to test changes to a
-- distribution\'s configuration before moving all of your domain\'s
-- production traffic to the new configuration.
module Amazonka.CloudFront.CreateContinuousDeploymentPolicy
  ( -- * Creating a Request
    CreateContinuousDeploymentPolicy (..),
    newCreateContinuousDeploymentPolicy,

    -- * Request Lenses
    createContinuousDeploymentPolicy_continuousDeploymentPolicyConfig,

    -- * Destructuring the Response
    CreateContinuousDeploymentPolicyResponse (..),
    newCreateContinuousDeploymentPolicyResponse,

    -- * Response Lenses
    createContinuousDeploymentPolicyResponse_continuousDeploymentPolicy,
    createContinuousDeploymentPolicyResponse_eTag,
    createContinuousDeploymentPolicyResponse_location,
    createContinuousDeploymentPolicyResponse_httpStatus,
  )
where

import Amazonka.CloudFront.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:/ 'newCreateContinuousDeploymentPolicy' smart constructor.
data CreateContinuousDeploymentPolicy = CreateContinuousDeploymentPolicy'
  { -- | Contains the configuration for a continuous deployment policy.
    CreateContinuousDeploymentPolicy
-> ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig :: ContinuousDeploymentPolicyConfig
  }
  deriving (CreateContinuousDeploymentPolicy
-> CreateContinuousDeploymentPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateContinuousDeploymentPolicy
-> CreateContinuousDeploymentPolicy -> Bool
$c/= :: CreateContinuousDeploymentPolicy
-> CreateContinuousDeploymentPolicy -> Bool
== :: CreateContinuousDeploymentPolicy
-> CreateContinuousDeploymentPolicy -> Bool
$c== :: CreateContinuousDeploymentPolicy
-> CreateContinuousDeploymentPolicy -> Bool
Prelude.Eq, ReadPrec [CreateContinuousDeploymentPolicy]
ReadPrec CreateContinuousDeploymentPolicy
Int -> ReadS CreateContinuousDeploymentPolicy
ReadS [CreateContinuousDeploymentPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateContinuousDeploymentPolicy]
$creadListPrec :: ReadPrec [CreateContinuousDeploymentPolicy]
readPrec :: ReadPrec CreateContinuousDeploymentPolicy
$creadPrec :: ReadPrec CreateContinuousDeploymentPolicy
readList :: ReadS [CreateContinuousDeploymentPolicy]
$creadList :: ReadS [CreateContinuousDeploymentPolicy]
readsPrec :: Int -> ReadS CreateContinuousDeploymentPolicy
$creadsPrec :: Int -> ReadS CreateContinuousDeploymentPolicy
Prelude.Read, Int -> CreateContinuousDeploymentPolicy -> ShowS
[CreateContinuousDeploymentPolicy] -> ShowS
CreateContinuousDeploymentPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateContinuousDeploymentPolicy] -> ShowS
$cshowList :: [CreateContinuousDeploymentPolicy] -> ShowS
show :: CreateContinuousDeploymentPolicy -> String
$cshow :: CreateContinuousDeploymentPolicy -> String
showsPrec :: Int -> CreateContinuousDeploymentPolicy -> ShowS
$cshowsPrec :: Int -> CreateContinuousDeploymentPolicy -> ShowS
Prelude.Show, forall x.
Rep CreateContinuousDeploymentPolicy x
-> CreateContinuousDeploymentPolicy
forall x.
CreateContinuousDeploymentPolicy
-> Rep CreateContinuousDeploymentPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateContinuousDeploymentPolicy x
-> CreateContinuousDeploymentPolicy
$cfrom :: forall x.
CreateContinuousDeploymentPolicy
-> Rep CreateContinuousDeploymentPolicy x
Prelude.Generic)

-- |
-- Create a value of 'CreateContinuousDeploymentPolicy' 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:
--
-- 'continuousDeploymentPolicyConfig', 'createContinuousDeploymentPolicy_continuousDeploymentPolicyConfig' - Contains the configuration for a continuous deployment policy.
newCreateContinuousDeploymentPolicy ::
  -- | 'continuousDeploymentPolicyConfig'
  ContinuousDeploymentPolicyConfig ->
  CreateContinuousDeploymentPolicy
newCreateContinuousDeploymentPolicy :: ContinuousDeploymentPolicyConfig
-> CreateContinuousDeploymentPolicy
newCreateContinuousDeploymentPolicy
  ContinuousDeploymentPolicyConfig
pContinuousDeploymentPolicyConfig_ =
    CreateContinuousDeploymentPolicy'
      { $sel:continuousDeploymentPolicyConfig:CreateContinuousDeploymentPolicy' :: ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig =
          ContinuousDeploymentPolicyConfig
pContinuousDeploymentPolicyConfig_
      }

-- | Contains the configuration for a continuous deployment policy.
createContinuousDeploymentPolicy_continuousDeploymentPolicyConfig :: Lens.Lens' CreateContinuousDeploymentPolicy ContinuousDeploymentPolicyConfig
createContinuousDeploymentPolicy_continuousDeploymentPolicyConfig :: Lens'
  CreateContinuousDeploymentPolicy ContinuousDeploymentPolicyConfig
createContinuousDeploymentPolicy_continuousDeploymentPolicyConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContinuousDeploymentPolicy' {ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig :: ContinuousDeploymentPolicyConfig
$sel:continuousDeploymentPolicyConfig:CreateContinuousDeploymentPolicy' :: CreateContinuousDeploymentPolicy
-> ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig} -> ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig) (\s :: CreateContinuousDeploymentPolicy
s@CreateContinuousDeploymentPolicy' {} ContinuousDeploymentPolicyConfig
a -> CreateContinuousDeploymentPolicy
s {$sel:continuousDeploymentPolicyConfig:CreateContinuousDeploymentPolicy' :: ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig = ContinuousDeploymentPolicyConfig
a} :: CreateContinuousDeploymentPolicy)

instance
  Core.AWSRequest
    CreateContinuousDeploymentPolicy
  where
  type
    AWSResponse CreateContinuousDeploymentPolicy =
      CreateContinuousDeploymentPolicyResponse
  request :: (Service -> Service)
-> CreateContinuousDeploymentPolicy
-> Request CreateContinuousDeploymentPolicy
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateContinuousDeploymentPolicy
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse CreateContinuousDeploymentPolicy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ContinuousDeploymentPolicy
-> Maybe Text
-> Maybe Text
-> Int
-> CreateContinuousDeploymentPolicyResponse
CreateContinuousDeploymentPolicyResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"ETag")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Location")
            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
    CreateContinuousDeploymentPolicy
  where
  hashWithSalt :: Int -> CreateContinuousDeploymentPolicy -> Int
hashWithSalt
    Int
_salt
    CreateContinuousDeploymentPolicy' {ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig :: ContinuousDeploymentPolicyConfig
$sel:continuousDeploymentPolicyConfig:CreateContinuousDeploymentPolicy' :: CreateContinuousDeploymentPolicy
-> ContinuousDeploymentPolicyConfig
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig

instance
  Prelude.NFData
    CreateContinuousDeploymentPolicy
  where
  rnf :: CreateContinuousDeploymentPolicy -> ()
rnf CreateContinuousDeploymentPolicy' {ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig :: ContinuousDeploymentPolicyConfig
$sel:continuousDeploymentPolicyConfig:CreateContinuousDeploymentPolicy' :: CreateContinuousDeploymentPolicy
-> ContinuousDeploymentPolicyConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig

instance
  Data.ToElement
    CreateContinuousDeploymentPolicy
  where
  toElement :: CreateContinuousDeploymentPolicy -> Element
toElement CreateContinuousDeploymentPolicy' {ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig :: ContinuousDeploymentPolicyConfig
$sel:continuousDeploymentPolicyConfig:CreateContinuousDeploymentPolicy' :: CreateContinuousDeploymentPolicy
-> ContinuousDeploymentPolicyConfig
..} =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://cloudfront.amazonaws.com/doc/2020-05-31/}ContinuousDeploymentPolicyConfig"
      ContinuousDeploymentPolicyConfig
continuousDeploymentPolicyConfig

instance
  Data.ToHeaders
    CreateContinuousDeploymentPolicy
  where
  toHeaders :: CreateContinuousDeploymentPolicy -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath CreateContinuousDeploymentPolicy where
  toPath :: CreateContinuousDeploymentPolicy -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/2020-05-31/continuous-deployment-policy"

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

-- | /See:/ 'newCreateContinuousDeploymentPolicyResponse' smart constructor.
data CreateContinuousDeploymentPolicyResponse = CreateContinuousDeploymentPolicyResponse'
  { -- | A continuous deployment policy.
    CreateContinuousDeploymentPolicyResponse
-> Maybe ContinuousDeploymentPolicy
continuousDeploymentPolicy :: Prelude.Maybe ContinuousDeploymentPolicy,
    -- | The version identifier for the current version of the continuous
    -- deployment policy.
    CreateContinuousDeploymentPolicyResponse -> Maybe Text
eTag :: Prelude.Maybe Prelude.Text,
    -- | The location of the continuous deployment policy.
    CreateContinuousDeploymentPolicyResponse -> Maybe Text
location :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateContinuousDeploymentPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateContinuousDeploymentPolicyResponse
-> CreateContinuousDeploymentPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateContinuousDeploymentPolicyResponse
-> CreateContinuousDeploymentPolicyResponse -> Bool
$c/= :: CreateContinuousDeploymentPolicyResponse
-> CreateContinuousDeploymentPolicyResponse -> Bool
== :: CreateContinuousDeploymentPolicyResponse
-> CreateContinuousDeploymentPolicyResponse -> Bool
$c== :: CreateContinuousDeploymentPolicyResponse
-> CreateContinuousDeploymentPolicyResponse -> Bool
Prelude.Eq, ReadPrec [CreateContinuousDeploymentPolicyResponse]
ReadPrec CreateContinuousDeploymentPolicyResponse
Int -> ReadS CreateContinuousDeploymentPolicyResponse
ReadS [CreateContinuousDeploymentPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateContinuousDeploymentPolicyResponse]
$creadListPrec :: ReadPrec [CreateContinuousDeploymentPolicyResponse]
readPrec :: ReadPrec CreateContinuousDeploymentPolicyResponse
$creadPrec :: ReadPrec CreateContinuousDeploymentPolicyResponse
readList :: ReadS [CreateContinuousDeploymentPolicyResponse]
$creadList :: ReadS [CreateContinuousDeploymentPolicyResponse]
readsPrec :: Int -> ReadS CreateContinuousDeploymentPolicyResponse
$creadsPrec :: Int -> ReadS CreateContinuousDeploymentPolicyResponse
Prelude.Read, Int -> CreateContinuousDeploymentPolicyResponse -> ShowS
[CreateContinuousDeploymentPolicyResponse] -> ShowS
CreateContinuousDeploymentPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateContinuousDeploymentPolicyResponse] -> ShowS
$cshowList :: [CreateContinuousDeploymentPolicyResponse] -> ShowS
show :: CreateContinuousDeploymentPolicyResponse -> String
$cshow :: CreateContinuousDeploymentPolicyResponse -> String
showsPrec :: Int -> CreateContinuousDeploymentPolicyResponse -> ShowS
$cshowsPrec :: Int -> CreateContinuousDeploymentPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep CreateContinuousDeploymentPolicyResponse x
-> CreateContinuousDeploymentPolicyResponse
forall x.
CreateContinuousDeploymentPolicyResponse
-> Rep CreateContinuousDeploymentPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateContinuousDeploymentPolicyResponse x
-> CreateContinuousDeploymentPolicyResponse
$cfrom :: forall x.
CreateContinuousDeploymentPolicyResponse
-> Rep CreateContinuousDeploymentPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateContinuousDeploymentPolicyResponse' 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:
--
-- 'continuousDeploymentPolicy', 'createContinuousDeploymentPolicyResponse_continuousDeploymentPolicy' - A continuous deployment policy.
--
-- 'eTag', 'createContinuousDeploymentPolicyResponse_eTag' - The version identifier for the current version of the continuous
-- deployment policy.
--
-- 'location', 'createContinuousDeploymentPolicyResponse_location' - The location of the continuous deployment policy.
--
-- 'httpStatus', 'createContinuousDeploymentPolicyResponse_httpStatus' - The response's http status code.
newCreateContinuousDeploymentPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateContinuousDeploymentPolicyResponse
newCreateContinuousDeploymentPolicyResponse :: Int -> CreateContinuousDeploymentPolicyResponse
newCreateContinuousDeploymentPolicyResponse
  Int
pHttpStatus_ =
    CreateContinuousDeploymentPolicyResponse'
      { $sel:continuousDeploymentPolicy:CreateContinuousDeploymentPolicyResponse' :: Maybe ContinuousDeploymentPolicy
continuousDeploymentPolicy =
          forall a. Maybe a
Prelude.Nothing,
        $sel:eTag:CreateContinuousDeploymentPolicyResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
        $sel:location:CreateContinuousDeploymentPolicyResponse' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:CreateContinuousDeploymentPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | A continuous deployment policy.
createContinuousDeploymentPolicyResponse_continuousDeploymentPolicy :: Lens.Lens' CreateContinuousDeploymentPolicyResponse (Prelude.Maybe ContinuousDeploymentPolicy)
createContinuousDeploymentPolicyResponse_continuousDeploymentPolicy :: Lens'
  CreateContinuousDeploymentPolicyResponse
  (Maybe ContinuousDeploymentPolicy)
createContinuousDeploymentPolicyResponse_continuousDeploymentPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContinuousDeploymentPolicyResponse' {Maybe ContinuousDeploymentPolicy
continuousDeploymentPolicy :: Maybe ContinuousDeploymentPolicy
$sel:continuousDeploymentPolicy:CreateContinuousDeploymentPolicyResponse' :: CreateContinuousDeploymentPolicyResponse
-> Maybe ContinuousDeploymentPolicy
continuousDeploymentPolicy} -> Maybe ContinuousDeploymentPolicy
continuousDeploymentPolicy) (\s :: CreateContinuousDeploymentPolicyResponse
s@CreateContinuousDeploymentPolicyResponse' {} Maybe ContinuousDeploymentPolicy
a -> CreateContinuousDeploymentPolicyResponse
s {$sel:continuousDeploymentPolicy:CreateContinuousDeploymentPolicyResponse' :: Maybe ContinuousDeploymentPolicy
continuousDeploymentPolicy = Maybe ContinuousDeploymentPolicy
a} :: CreateContinuousDeploymentPolicyResponse)

-- | The version identifier for the current version of the continuous
-- deployment policy.
createContinuousDeploymentPolicyResponse_eTag :: Lens.Lens' CreateContinuousDeploymentPolicyResponse (Prelude.Maybe Prelude.Text)
createContinuousDeploymentPolicyResponse_eTag :: Lens' CreateContinuousDeploymentPolicyResponse (Maybe Text)
createContinuousDeploymentPolicyResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContinuousDeploymentPolicyResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:CreateContinuousDeploymentPolicyResponse' :: CreateContinuousDeploymentPolicyResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: CreateContinuousDeploymentPolicyResponse
s@CreateContinuousDeploymentPolicyResponse' {} Maybe Text
a -> CreateContinuousDeploymentPolicyResponse
s {$sel:eTag:CreateContinuousDeploymentPolicyResponse' :: Maybe Text
eTag = Maybe Text
a} :: CreateContinuousDeploymentPolicyResponse)

-- | The location of the continuous deployment policy.
createContinuousDeploymentPolicyResponse_location :: Lens.Lens' CreateContinuousDeploymentPolicyResponse (Prelude.Maybe Prelude.Text)
createContinuousDeploymentPolicyResponse_location :: Lens' CreateContinuousDeploymentPolicyResponse (Maybe Text)
createContinuousDeploymentPolicyResponse_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContinuousDeploymentPolicyResponse' {Maybe Text
location :: Maybe Text
$sel:location:CreateContinuousDeploymentPolicyResponse' :: CreateContinuousDeploymentPolicyResponse -> Maybe Text
location} -> Maybe Text
location) (\s :: CreateContinuousDeploymentPolicyResponse
s@CreateContinuousDeploymentPolicyResponse' {} Maybe Text
a -> CreateContinuousDeploymentPolicyResponse
s {$sel:location:CreateContinuousDeploymentPolicyResponse' :: Maybe Text
location = Maybe Text
a} :: CreateContinuousDeploymentPolicyResponse)

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

instance
  Prelude.NFData
    CreateContinuousDeploymentPolicyResponse
  where
  rnf :: CreateContinuousDeploymentPolicyResponse -> ()
rnf CreateContinuousDeploymentPolicyResponse' {Int
Maybe Text
Maybe ContinuousDeploymentPolicy
httpStatus :: Int
location :: Maybe Text
eTag :: Maybe Text
continuousDeploymentPolicy :: Maybe ContinuousDeploymentPolicy
$sel:httpStatus:CreateContinuousDeploymentPolicyResponse' :: CreateContinuousDeploymentPolicyResponse -> Int
$sel:location:CreateContinuousDeploymentPolicyResponse' :: CreateContinuousDeploymentPolicyResponse -> Maybe Text
$sel:eTag:CreateContinuousDeploymentPolicyResponse' :: CreateContinuousDeploymentPolicyResponse -> Maybe Text
$sel:continuousDeploymentPolicy:CreateContinuousDeploymentPolicyResponse' :: CreateContinuousDeploymentPolicyResponse
-> Maybe ContinuousDeploymentPolicy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ContinuousDeploymentPolicy
continuousDeploymentPolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eTag
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus