{-# 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.ElasticBeanstalk.SwapEnvironmentCNAMEs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Swaps the CNAMEs of two environments.
module Amazonka.ElasticBeanstalk.SwapEnvironmentCNAMEs
  ( -- * Creating a Request
    SwapEnvironmentCNAMEs (..),
    newSwapEnvironmentCNAMEs,

    -- * Request Lenses
    swapEnvironmentCNAMEs_destinationEnvironmentId,
    swapEnvironmentCNAMEs_destinationEnvironmentName,
    swapEnvironmentCNAMEs_sourceEnvironmentId,
    swapEnvironmentCNAMEs_sourceEnvironmentName,

    -- * Destructuring the Response
    SwapEnvironmentCNAMEsResponse (..),
    newSwapEnvironmentCNAMEsResponse,
  )
where

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

-- | Swaps the CNAMEs of two environments.
--
-- /See:/ 'newSwapEnvironmentCNAMEs' smart constructor.
data SwapEnvironmentCNAMEs = SwapEnvironmentCNAMEs'
  { -- | The ID of the destination environment.
    --
    -- Condition: You must specify at least the @DestinationEnvironmentID@ or
    -- the @DestinationEnvironmentName@. You may also specify both. You must
    -- specify the @SourceEnvironmentId@ with the @DestinationEnvironmentId@.
    SwapEnvironmentCNAMEs -> Maybe Text
destinationEnvironmentId :: Prelude.Maybe Prelude.Text,
    -- | The name of the destination environment.
    --
    -- Condition: You must specify at least the @DestinationEnvironmentID@ or
    -- the @DestinationEnvironmentName@. You may also specify both. You must
    -- specify the @SourceEnvironmentName@ with the
    -- @DestinationEnvironmentName@.
    SwapEnvironmentCNAMEs -> Maybe Text
destinationEnvironmentName :: Prelude.Maybe Prelude.Text,
    -- | The ID of the source environment.
    --
    -- Condition: You must specify at least the @SourceEnvironmentID@ or the
    -- @SourceEnvironmentName@. You may also specify both. If you specify the
    -- @SourceEnvironmentId@, you must specify the @DestinationEnvironmentId@.
    SwapEnvironmentCNAMEs -> Maybe Text
sourceEnvironmentId :: Prelude.Maybe Prelude.Text,
    -- | The name of the source environment.
    --
    -- Condition: You must specify at least the @SourceEnvironmentID@ or the
    -- @SourceEnvironmentName@. You may also specify both. If you specify the
    -- @SourceEnvironmentName@, you must specify the
    -- @DestinationEnvironmentName@.
    SwapEnvironmentCNAMEs -> Maybe Text
sourceEnvironmentName :: Prelude.Maybe Prelude.Text
  }
  deriving (SwapEnvironmentCNAMEs -> SwapEnvironmentCNAMEs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapEnvironmentCNAMEs -> SwapEnvironmentCNAMEs -> Bool
$c/= :: SwapEnvironmentCNAMEs -> SwapEnvironmentCNAMEs -> Bool
== :: SwapEnvironmentCNAMEs -> SwapEnvironmentCNAMEs -> Bool
$c== :: SwapEnvironmentCNAMEs -> SwapEnvironmentCNAMEs -> Bool
Prelude.Eq, ReadPrec [SwapEnvironmentCNAMEs]
ReadPrec SwapEnvironmentCNAMEs
Int -> ReadS SwapEnvironmentCNAMEs
ReadS [SwapEnvironmentCNAMEs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SwapEnvironmentCNAMEs]
$creadListPrec :: ReadPrec [SwapEnvironmentCNAMEs]
readPrec :: ReadPrec SwapEnvironmentCNAMEs
$creadPrec :: ReadPrec SwapEnvironmentCNAMEs
readList :: ReadS [SwapEnvironmentCNAMEs]
$creadList :: ReadS [SwapEnvironmentCNAMEs]
readsPrec :: Int -> ReadS SwapEnvironmentCNAMEs
$creadsPrec :: Int -> ReadS SwapEnvironmentCNAMEs
Prelude.Read, Int -> SwapEnvironmentCNAMEs -> ShowS
[SwapEnvironmentCNAMEs] -> ShowS
SwapEnvironmentCNAMEs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwapEnvironmentCNAMEs] -> ShowS
$cshowList :: [SwapEnvironmentCNAMEs] -> ShowS
show :: SwapEnvironmentCNAMEs -> String
$cshow :: SwapEnvironmentCNAMEs -> String
showsPrec :: Int -> SwapEnvironmentCNAMEs -> ShowS
$cshowsPrec :: Int -> SwapEnvironmentCNAMEs -> ShowS
Prelude.Show, forall x. Rep SwapEnvironmentCNAMEs x -> SwapEnvironmentCNAMEs
forall x. SwapEnvironmentCNAMEs -> Rep SwapEnvironmentCNAMEs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SwapEnvironmentCNAMEs x -> SwapEnvironmentCNAMEs
$cfrom :: forall x. SwapEnvironmentCNAMEs -> Rep SwapEnvironmentCNAMEs x
Prelude.Generic)

-- |
-- Create a value of 'SwapEnvironmentCNAMEs' 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:
--
-- 'destinationEnvironmentId', 'swapEnvironmentCNAMEs_destinationEnvironmentId' - The ID of the destination environment.
--
-- Condition: You must specify at least the @DestinationEnvironmentID@ or
-- the @DestinationEnvironmentName@. You may also specify both. You must
-- specify the @SourceEnvironmentId@ with the @DestinationEnvironmentId@.
--
-- 'destinationEnvironmentName', 'swapEnvironmentCNAMEs_destinationEnvironmentName' - The name of the destination environment.
--
-- Condition: You must specify at least the @DestinationEnvironmentID@ or
-- the @DestinationEnvironmentName@. You may also specify both. You must
-- specify the @SourceEnvironmentName@ with the
-- @DestinationEnvironmentName@.
--
-- 'sourceEnvironmentId', 'swapEnvironmentCNAMEs_sourceEnvironmentId' - The ID of the source environment.
--
-- Condition: You must specify at least the @SourceEnvironmentID@ or the
-- @SourceEnvironmentName@. You may also specify both. If you specify the
-- @SourceEnvironmentId@, you must specify the @DestinationEnvironmentId@.
--
-- 'sourceEnvironmentName', 'swapEnvironmentCNAMEs_sourceEnvironmentName' - The name of the source environment.
--
-- Condition: You must specify at least the @SourceEnvironmentID@ or the
-- @SourceEnvironmentName@. You may also specify both. If you specify the
-- @SourceEnvironmentName@, you must specify the
-- @DestinationEnvironmentName@.
newSwapEnvironmentCNAMEs ::
  SwapEnvironmentCNAMEs
newSwapEnvironmentCNAMEs :: SwapEnvironmentCNAMEs
newSwapEnvironmentCNAMEs =
  SwapEnvironmentCNAMEs'
    { $sel:destinationEnvironmentId:SwapEnvironmentCNAMEs' :: Maybe Text
destinationEnvironmentId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:destinationEnvironmentName:SwapEnvironmentCNAMEs' :: Maybe Text
destinationEnvironmentName = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceEnvironmentId:SwapEnvironmentCNAMEs' :: Maybe Text
sourceEnvironmentId = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceEnvironmentName:SwapEnvironmentCNAMEs' :: Maybe Text
sourceEnvironmentName = forall a. Maybe a
Prelude.Nothing
    }

-- | The ID of the destination environment.
--
-- Condition: You must specify at least the @DestinationEnvironmentID@ or
-- the @DestinationEnvironmentName@. You may also specify both. You must
-- specify the @SourceEnvironmentId@ with the @DestinationEnvironmentId@.
swapEnvironmentCNAMEs_destinationEnvironmentId :: Lens.Lens' SwapEnvironmentCNAMEs (Prelude.Maybe Prelude.Text)
swapEnvironmentCNAMEs_destinationEnvironmentId :: Lens' SwapEnvironmentCNAMEs (Maybe Text)
swapEnvironmentCNAMEs_destinationEnvironmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SwapEnvironmentCNAMEs' {Maybe Text
destinationEnvironmentId :: Maybe Text
$sel:destinationEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
destinationEnvironmentId} -> Maybe Text
destinationEnvironmentId) (\s :: SwapEnvironmentCNAMEs
s@SwapEnvironmentCNAMEs' {} Maybe Text
a -> SwapEnvironmentCNAMEs
s {$sel:destinationEnvironmentId:SwapEnvironmentCNAMEs' :: Maybe Text
destinationEnvironmentId = Maybe Text
a} :: SwapEnvironmentCNAMEs)

-- | The name of the destination environment.
--
-- Condition: You must specify at least the @DestinationEnvironmentID@ or
-- the @DestinationEnvironmentName@. You may also specify both. You must
-- specify the @SourceEnvironmentName@ with the
-- @DestinationEnvironmentName@.
swapEnvironmentCNAMEs_destinationEnvironmentName :: Lens.Lens' SwapEnvironmentCNAMEs (Prelude.Maybe Prelude.Text)
swapEnvironmentCNAMEs_destinationEnvironmentName :: Lens' SwapEnvironmentCNAMEs (Maybe Text)
swapEnvironmentCNAMEs_destinationEnvironmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SwapEnvironmentCNAMEs' {Maybe Text
destinationEnvironmentName :: Maybe Text
$sel:destinationEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
destinationEnvironmentName} -> Maybe Text
destinationEnvironmentName) (\s :: SwapEnvironmentCNAMEs
s@SwapEnvironmentCNAMEs' {} Maybe Text
a -> SwapEnvironmentCNAMEs
s {$sel:destinationEnvironmentName:SwapEnvironmentCNAMEs' :: Maybe Text
destinationEnvironmentName = Maybe Text
a} :: SwapEnvironmentCNAMEs)

-- | The ID of the source environment.
--
-- Condition: You must specify at least the @SourceEnvironmentID@ or the
-- @SourceEnvironmentName@. You may also specify both. If you specify the
-- @SourceEnvironmentId@, you must specify the @DestinationEnvironmentId@.
swapEnvironmentCNAMEs_sourceEnvironmentId :: Lens.Lens' SwapEnvironmentCNAMEs (Prelude.Maybe Prelude.Text)
swapEnvironmentCNAMEs_sourceEnvironmentId :: Lens' SwapEnvironmentCNAMEs (Maybe Text)
swapEnvironmentCNAMEs_sourceEnvironmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SwapEnvironmentCNAMEs' {Maybe Text
sourceEnvironmentId :: Maybe Text
$sel:sourceEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
sourceEnvironmentId} -> Maybe Text
sourceEnvironmentId) (\s :: SwapEnvironmentCNAMEs
s@SwapEnvironmentCNAMEs' {} Maybe Text
a -> SwapEnvironmentCNAMEs
s {$sel:sourceEnvironmentId:SwapEnvironmentCNAMEs' :: Maybe Text
sourceEnvironmentId = Maybe Text
a} :: SwapEnvironmentCNAMEs)

-- | The name of the source environment.
--
-- Condition: You must specify at least the @SourceEnvironmentID@ or the
-- @SourceEnvironmentName@. You may also specify both. If you specify the
-- @SourceEnvironmentName@, you must specify the
-- @DestinationEnvironmentName@.
swapEnvironmentCNAMEs_sourceEnvironmentName :: Lens.Lens' SwapEnvironmentCNAMEs (Prelude.Maybe Prelude.Text)
swapEnvironmentCNAMEs_sourceEnvironmentName :: Lens' SwapEnvironmentCNAMEs (Maybe Text)
swapEnvironmentCNAMEs_sourceEnvironmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SwapEnvironmentCNAMEs' {Maybe Text
sourceEnvironmentName :: Maybe Text
$sel:sourceEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
sourceEnvironmentName} -> Maybe Text
sourceEnvironmentName) (\s :: SwapEnvironmentCNAMEs
s@SwapEnvironmentCNAMEs' {} Maybe Text
a -> SwapEnvironmentCNAMEs
s {$sel:sourceEnvironmentName:SwapEnvironmentCNAMEs' :: Maybe Text
sourceEnvironmentName = Maybe Text
a} :: SwapEnvironmentCNAMEs)

instance Core.AWSRequest SwapEnvironmentCNAMEs where
  type
    AWSResponse SwapEnvironmentCNAMEs =
      SwapEnvironmentCNAMEsResponse
  request :: (Service -> Service)
-> SwapEnvironmentCNAMEs -> Request SwapEnvironmentCNAMEs
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy SwapEnvironmentCNAMEs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SwapEnvironmentCNAMEs)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull SwapEnvironmentCNAMEsResponse
SwapEnvironmentCNAMEsResponse'

instance Prelude.Hashable SwapEnvironmentCNAMEs where
  hashWithSalt :: Int -> SwapEnvironmentCNAMEs -> Int
hashWithSalt Int
_salt SwapEnvironmentCNAMEs' {Maybe Text
sourceEnvironmentName :: Maybe Text
sourceEnvironmentId :: Maybe Text
destinationEnvironmentName :: Maybe Text
destinationEnvironmentId :: Maybe Text
$sel:sourceEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:sourceEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:destinationEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:destinationEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationEnvironmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationEnvironmentName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceEnvironmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceEnvironmentName

instance Prelude.NFData SwapEnvironmentCNAMEs where
  rnf :: SwapEnvironmentCNAMEs -> ()
rnf SwapEnvironmentCNAMEs' {Maybe Text
sourceEnvironmentName :: Maybe Text
sourceEnvironmentId :: Maybe Text
destinationEnvironmentName :: Maybe Text
destinationEnvironmentId :: Maybe Text
$sel:sourceEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:sourceEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:destinationEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:destinationEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationEnvironmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationEnvironmentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceEnvironmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceEnvironmentName

instance Data.ToHeaders SwapEnvironmentCNAMEs where
  toHeaders :: SwapEnvironmentCNAMEs -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery SwapEnvironmentCNAMEs where
  toQuery :: SwapEnvironmentCNAMEs -> QueryString
toQuery SwapEnvironmentCNAMEs' {Maybe Text
sourceEnvironmentName :: Maybe Text
sourceEnvironmentId :: Maybe Text
destinationEnvironmentName :: Maybe Text
destinationEnvironmentId :: Maybe Text
$sel:sourceEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:sourceEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:destinationEnvironmentName:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
$sel:destinationEnvironmentId:SwapEnvironmentCNAMEs' :: SwapEnvironmentCNAMEs -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"SwapEnvironmentCNAMEs" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"DestinationEnvironmentId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationEnvironmentId,
        ByteString
"DestinationEnvironmentName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationEnvironmentName,
        ByteString
"SourceEnvironmentId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
sourceEnvironmentId,
        ByteString
"SourceEnvironmentName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
sourceEnvironmentName
      ]

-- | /See:/ 'newSwapEnvironmentCNAMEsResponse' smart constructor.
data SwapEnvironmentCNAMEsResponse = SwapEnvironmentCNAMEsResponse'
  {
  }
  deriving (SwapEnvironmentCNAMEsResponse
-> SwapEnvironmentCNAMEsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapEnvironmentCNAMEsResponse
-> SwapEnvironmentCNAMEsResponse -> Bool
$c/= :: SwapEnvironmentCNAMEsResponse
-> SwapEnvironmentCNAMEsResponse -> Bool
== :: SwapEnvironmentCNAMEsResponse
-> SwapEnvironmentCNAMEsResponse -> Bool
$c== :: SwapEnvironmentCNAMEsResponse
-> SwapEnvironmentCNAMEsResponse -> Bool
Prelude.Eq, ReadPrec [SwapEnvironmentCNAMEsResponse]
ReadPrec SwapEnvironmentCNAMEsResponse
Int -> ReadS SwapEnvironmentCNAMEsResponse
ReadS [SwapEnvironmentCNAMEsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SwapEnvironmentCNAMEsResponse]
$creadListPrec :: ReadPrec [SwapEnvironmentCNAMEsResponse]
readPrec :: ReadPrec SwapEnvironmentCNAMEsResponse
$creadPrec :: ReadPrec SwapEnvironmentCNAMEsResponse
readList :: ReadS [SwapEnvironmentCNAMEsResponse]
$creadList :: ReadS [SwapEnvironmentCNAMEsResponse]
readsPrec :: Int -> ReadS SwapEnvironmentCNAMEsResponse
$creadsPrec :: Int -> ReadS SwapEnvironmentCNAMEsResponse
Prelude.Read, Int -> SwapEnvironmentCNAMEsResponse -> ShowS
[SwapEnvironmentCNAMEsResponse] -> ShowS
SwapEnvironmentCNAMEsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwapEnvironmentCNAMEsResponse] -> ShowS
$cshowList :: [SwapEnvironmentCNAMEsResponse] -> ShowS
show :: SwapEnvironmentCNAMEsResponse -> String
$cshow :: SwapEnvironmentCNAMEsResponse -> String
showsPrec :: Int -> SwapEnvironmentCNAMEsResponse -> ShowS
$cshowsPrec :: Int -> SwapEnvironmentCNAMEsResponse -> ShowS
Prelude.Show, forall x.
Rep SwapEnvironmentCNAMEsResponse x
-> SwapEnvironmentCNAMEsResponse
forall x.
SwapEnvironmentCNAMEsResponse
-> Rep SwapEnvironmentCNAMEsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SwapEnvironmentCNAMEsResponse x
-> SwapEnvironmentCNAMEsResponse
$cfrom :: forall x.
SwapEnvironmentCNAMEsResponse
-> Rep SwapEnvironmentCNAMEsResponse x
Prelude.Generic)

-- |
-- Create a value of 'SwapEnvironmentCNAMEsResponse' 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.
newSwapEnvironmentCNAMEsResponse ::
  SwapEnvironmentCNAMEsResponse
newSwapEnvironmentCNAMEsResponse :: SwapEnvironmentCNAMEsResponse
newSwapEnvironmentCNAMEsResponse =
  SwapEnvironmentCNAMEsResponse
SwapEnvironmentCNAMEsResponse'

instance Prelude.NFData SwapEnvironmentCNAMEsResponse where
  rnf :: SwapEnvironmentCNAMEsResponse -> ()
rnf SwapEnvironmentCNAMEsResponse
_ = ()