{-# 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.PinpointEmail.CreateConfigurationSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create a configuration set. /Configuration sets/ are groups of rules
-- that you can apply to the emails you send using Amazon Pinpoint. You
-- apply a configuration set to an email by including a reference to the
-- configuration set in the headers of the email. When you apply a
-- configuration set to an email, all of the rules in that configuration
-- set are applied to the email.
module Amazonka.PinpointEmail.CreateConfigurationSet
  ( -- * Creating a Request
    CreateConfigurationSet (..),
    newCreateConfigurationSet,

    -- * Request Lenses
    createConfigurationSet_deliveryOptions,
    createConfigurationSet_reputationOptions,
    createConfigurationSet_sendingOptions,
    createConfigurationSet_tags,
    createConfigurationSet_trackingOptions,
    createConfigurationSet_configurationSetName,

    -- * Destructuring the Response
    CreateConfigurationSetResponse (..),
    newCreateConfigurationSetResponse,

    -- * Response Lenses
    createConfigurationSetResponse_httpStatus,
  )
where

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

-- | A request to create a configuration set.
--
-- /See:/ 'newCreateConfigurationSet' smart constructor.
data CreateConfigurationSet = CreateConfigurationSet'
  { -- | An object that defines the dedicated IP pool that is used to send emails
    -- that you send using the configuration set.
    CreateConfigurationSet -> Maybe DeliveryOptions
deliveryOptions :: Prelude.Maybe DeliveryOptions,
    -- | An object that defines whether or not Amazon Pinpoint collects
    -- reputation metrics for the emails that you send that use the
    -- configuration set.
    CreateConfigurationSet -> Maybe ReputationOptions
reputationOptions :: Prelude.Maybe ReputationOptions,
    -- | An object that defines whether or not Amazon Pinpoint can send email
    -- that you send using the configuration set.
    CreateConfigurationSet -> Maybe SendingOptions
sendingOptions :: Prelude.Maybe SendingOptions,
    -- | An array of objects that define the tags (keys and values) that you want
    -- to associate with the configuration set.
    CreateConfigurationSet -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | An object that defines the open and click tracking options for emails
    -- that you send using the configuration set.
    CreateConfigurationSet -> Maybe TrackingOptions
trackingOptions :: Prelude.Maybe TrackingOptions,
    -- | The name of the configuration set.
    CreateConfigurationSet -> Text
configurationSetName :: Prelude.Text
  }
  deriving (CreateConfigurationSet -> CreateConfigurationSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConfigurationSet -> CreateConfigurationSet -> Bool
$c/= :: CreateConfigurationSet -> CreateConfigurationSet -> Bool
== :: CreateConfigurationSet -> CreateConfigurationSet -> Bool
$c== :: CreateConfigurationSet -> CreateConfigurationSet -> Bool
Prelude.Eq, ReadPrec [CreateConfigurationSet]
ReadPrec CreateConfigurationSet
Int -> ReadS CreateConfigurationSet
ReadS [CreateConfigurationSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateConfigurationSet]
$creadListPrec :: ReadPrec [CreateConfigurationSet]
readPrec :: ReadPrec CreateConfigurationSet
$creadPrec :: ReadPrec CreateConfigurationSet
readList :: ReadS [CreateConfigurationSet]
$creadList :: ReadS [CreateConfigurationSet]
readsPrec :: Int -> ReadS CreateConfigurationSet
$creadsPrec :: Int -> ReadS CreateConfigurationSet
Prelude.Read, Int -> CreateConfigurationSet -> ShowS
[CreateConfigurationSet] -> ShowS
CreateConfigurationSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConfigurationSet] -> ShowS
$cshowList :: [CreateConfigurationSet] -> ShowS
show :: CreateConfigurationSet -> String
$cshow :: CreateConfigurationSet -> String
showsPrec :: Int -> CreateConfigurationSet -> ShowS
$cshowsPrec :: Int -> CreateConfigurationSet -> ShowS
Prelude.Show, forall x. Rep CreateConfigurationSet x -> CreateConfigurationSet
forall x. CreateConfigurationSet -> Rep CreateConfigurationSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateConfigurationSet x -> CreateConfigurationSet
$cfrom :: forall x. CreateConfigurationSet -> Rep CreateConfigurationSet x
Prelude.Generic)

-- |
-- Create a value of 'CreateConfigurationSet' 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:
--
-- 'deliveryOptions', 'createConfigurationSet_deliveryOptions' - An object that defines the dedicated IP pool that is used to send emails
-- that you send using the configuration set.
--
-- 'reputationOptions', 'createConfigurationSet_reputationOptions' - An object that defines whether or not Amazon Pinpoint collects
-- reputation metrics for the emails that you send that use the
-- configuration set.
--
-- 'sendingOptions', 'createConfigurationSet_sendingOptions' - An object that defines whether or not Amazon Pinpoint can send email
-- that you send using the configuration set.
--
-- 'tags', 'createConfigurationSet_tags' - An array of objects that define the tags (keys and values) that you want
-- to associate with the configuration set.
--
-- 'trackingOptions', 'createConfigurationSet_trackingOptions' - An object that defines the open and click tracking options for emails
-- that you send using the configuration set.
--
-- 'configurationSetName', 'createConfigurationSet_configurationSetName' - The name of the configuration set.
newCreateConfigurationSet ::
  -- | 'configurationSetName'
  Prelude.Text ->
  CreateConfigurationSet
newCreateConfigurationSet :: Text -> CreateConfigurationSet
newCreateConfigurationSet Text
pConfigurationSetName_ =
  CreateConfigurationSet'
    { $sel:deliveryOptions:CreateConfigurationSet' :: Maybe DeliveryOptions
deliveryOptions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:reputationOptions:CreateConfigurationSet' :: Maybe ReputationOptions
reputationOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:sendingOptions:CreateConfigurationSet' :: Maybe SendingOptions
sendingOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateConfigurationSet' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:trackingOptions:CreateConfigurationSet' :: Maybe TrackingOptions
trackingOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationSetName:CreateConfigurationSet' :: Text
configurationSetName = Text
pConfigurationSetName_
    }

-- | An object that defines the dedicated IP pool that is used to send emails
-- that you send using the configuration set.
createConfigurationSet_deliveryOptions :: Lens.Lens' CreateConfigurationSet (Prelude.Maybe DeliveryOptions)
createConfigurationSet_deliveryOptions :: Lens' CreateConfigurationSet (Maybe DeliveryOptions)
createConfigurationSet_deliveryOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationSet' {Maybe DeliveryOptions
deliveryOptions :: Maybe DeliveryOptions
$sel:deliveryOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe DeliveryOptions
deliveryOptions} -> Maybe DeliveryOptions
deliveryOptions) (\s :: CreateConfigurationSet
s@CreateConfigurationSet' {} Maybe DeliveryOptions
a -> CreateConfigurationSet
s {$sel:deliveryOptions:CreateConfigurationSet' :: Maybe DeliveryOptions
deliveryOptions = Maybe DeliveryOptions
a} :: CreateConfigurationSet)

-- | An object that defines whether or not Amazon Pinpoint collects
-- reputation metrics for the emails that you send that use the
-- configuration set.
createConfigurationSet_reputationOptions :: Lens.Lens' CreateConfigurationSet (Prelude.Maybe ReputationOptions)
createConfigurationSet_reputationOptions :: Lens' CreateConfigurationSet (Maybe ReputationOptions)
createConfigurationSet_reputationOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationSet' {Maybe ReputationOptions
reputationOptions :: Maybe ReputationOptions
$sel:reputationOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe ReputationOptions
reputationOptions} -> Maybe ReputationOptions
reputationOptions) (\s :: CreateConfigurationSet
s@CreateConfigurationSet' {} Maybe ReputationOptions
a -> CreateConfigurationSet
s {$sel:reputationOptions:CreateConfigurationSet' :: Maybe ReputationOptions
reputationOptions = Maybe ReputationOptions
a} :: CreateConfigurationSet)

-- | An object that defines whether or not Amazon Pinpoint can send email
-- that you send using the configuration set.
createConfigurationSet_sendingOptions :: Lens.Lens' CreateConfigurationSet (Prelude.Maybe SendingOptions)
createConfigurationSet_sendingOptions :: Lens' CreateConfigurationSet (Maybe SendingOptions)
createConfigurationSet_sendingOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationSet' {Maybe SendingOptions
sendingOptions :: Maybe SendingOptions
$sel:sendingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe SendingOptions
sendingOptions} -> Maybe SendingOptions
sendingOptions) (\s :: CreateConfigurationSet
s@CreateConfigurationSet' {} Maybe SendingOptions
a -> CreateConfigurationSet
s {$sel:sendingOptions:CreateConfigurationSet' :: Maybe SendingOptions
sendingOptions = Maybe SendingOptions
a} :: CreateConfigurationSet)

-- | An array of objects that define the tags (keys and values) that you want
-- to associate with the configuration set.
createConfigurationSet_tags :: Lens.Lens' CreateConfigurationSet (Prelude.Maybe [Tag])
createConfigurationSet_tags :: Lens' CreateConfigurationSet (Maybe [Tag])
createConfigurationSet_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationSet' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateConfigurationSet
s@CreateConfigurationSet' {} Maybe [Tag]
a -> CreateConfigurationSet
s {$sel:tags:CreateConfigurationSet' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateConfigurationSet) 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

-- | An object that defines the open and click tracking options for emails
-- that you send using the configuration set.
createConfigurationSet_trackingOptions :: Lens.Lens' CreateConfigurationSet (Prelude.Maybe TrackingOptions)
createConfigurationSet_trackingOptions :: Lens' CreateConfigurationSet (Maybe TrackingOptions)
createConfigurationSet_trackingOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationSet' {Maybe TrackingOptions
trackingOptions :: Maybe TrackingOptions
$sel:trackingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe TrackingOptions
trackingOptions} -> Maybe TrackingOptions
trackingOptions) (\s :: CreateConfigurationSet
s@CreateConfigurationSet' {} Maybe TrackingOptions
a -> CreateConfigurationSet
s {$sel:trackingOptions:CreateConfigurationSet' :: Maybe TrackingOptions
trackingOptions = Maybe TrackingOptions
a} :: CreateConfigurationSet)

-- | The name of the configuration set.
createConfigurationSet_configurationSetName :: Lens.Lens' CreateConfigurationSet Prelude.Text
createConfigurationSet_configurationSetName :: Lens' CreateConfigurationSet Text
createConfigurationSet_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationSet' {Text
configurationSetName :: Text
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Text
configurationSetName} -> Text
configurationSetName) (\s :: CreateConfigurationSet
s@CreateConfigurationSet' {} Text
a -> CreateConfigurationSet
s {$sel:configurationSetName:CreateConfigurationSet' :: Text
configurationSetName = Text
a} :: CreateConfigurationSet)

instance Core.AWSRequest CreateConfigurationSet where
  type
    AWSResponse CreateConfigurationSet =
      CreateConfigurationSetResponse
  request :: (Service -> Service)
-> CreateConfigurationSet -> Request CreateConfigurationSet
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 CreateConfigurationSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateConfigurationSet)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> CreateConfigurationSetResponse
CreateConfigurationSetResponse'
            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))
      )

instance Prelude.Hashable CreateConfigurationSet where
  hashWithSalt :: Int -> CreateConfigurationSet -> Int
hashWithSalt Int
_salt CreateConfigurationSet' {Maybe [Tag]
Maybe ReputationOptions
Maybe SendingOptions
Maybe DeliveryOptions
Maybe TrackingOptions
Text
configurationSetName :: Text
trackingOptions :: Maybe TrackingOptions
tags :: Maybe [Tag]
sendingOptions :: Maybe SendingOptions
reputationOptions :: Maybe ReputationOptions
deliveryOptions :: Maybe DeliveryOptions
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Text
$sel:trackingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe TrackingOptions
$sel:tags:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe [Tag]
$sel:sendingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe SendingOptions
$sel:reputationOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe ReputationOptions
$sel:deliveryOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe DeliveryOptions
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeliveryOptions
deliveryOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReputationOptions
reputationOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SendingOptions
sendingOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrackingOptions
trackingOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationSetName

instance Prelude.NFData CreateConfigurationSet where
  rnf :: CreateConfigurationSet -> ()
rnf CreateConfigurationSet' {Maybe [Tag]
Maybe ReputationOptions
Maybe SendingOptions
Maybe DeliveryOptions
Maybe TrackingOptions
Text
configurationSetName :: Text
trackingOptions :: Maybe TrackingOptions
tags :: Maybe [Tag]
sendingOptions :: Maybe SendingOptions
reputationOptions :: Maybe ReputationOptions
deliveryOptions :: Maybe DeliveryOptions
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Text
$sel:trackingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe TrackingOptions
$sel:tags:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe [Tag]
$sel:sendingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe SendingOptions
$sel:reputationOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe ReputationOptions
$sel:deliveryOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe DeliveryOptions
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DeliveryOptions
deliveryOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReputationOptions
reputationOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SendingOptions
sendingOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrackingOptions
trackingOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configurationSetName

instance Data.ToHeaders CreateConfigurationSet where
  toHeaders :: CreateConfigurationSet -> 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 CreateConfigurationSet where
  toJSON :: CreateConfigurationSet -> Value
toJSON CreateConfigurationSet' {Maybe [Tag]
Maybe ReputationOptions
Maybe SendingOptions
Maybe DeliveryOptions
Maybe TrackingOptions
Text
configurationSetName :: Text
trackingOptions :: Maybe TrackingOptions
tags :: Maybe [Tag]
sendingOptions :: Maybe SendingOptions
reputationOptions :: Maybe ReputationOptions
deliveryOptions :: Maybe DeliveryOptions
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Text
$sel:trackingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe TrackingOptions
$sel:tags:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe [Tag]
$sel:sendingOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe SendingOptions
$sel:reputationOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe ReputationOptions
$sel:deliveryOptions:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe DeliveryOptions
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DeliveryOptions" 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 DeliveryOptions
deliveryOptions,
            (Key
"ReputationOptions" 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 ReputationOptions
reputationOptions,
            (Key
"SendingOptions" 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 SendingOptions
sendingOptions,
            (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 [Tag]
tags,
            (Key
"TrackingOptions" 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 TrackingOptions
trackingOptions,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"ConfigurationSetName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
configurationSetName
              )
          ]
      )

instance Data.ToPath CreateConfigurationSet where
  toPath :: CreateConfigurationSet -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/email/configuration-sets"

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

-- | An HTTP 200 response if the request succeeds, or an error message if the
-- request fails.
--
-- /See:/ 'newCreateConfigurationSetResponse' smart constructor.
data CreateConfigurationSetResponse = CreateConfigurationSetResponse'
  { -- | The response's http status code.
    CreateConfigurationSetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateConfigurationSetResponse
-> CreateConfigurationSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConfigurationSetResponse
-> CreateConfigurationSetResponse -> Bool
$c/= :: CreateConfigurationSetResponse
-> CreateConfigurationSetResponse -> Bool
== :: CreateConfigurationSetResponse
-> CreateConfigurationSetResponse -> Bool
$c== :: CreateConfigurationSetResponse
-> CreateConfigurationSetResponse -> Bool
Prelude.Eq, ReadPrec [CreateConfigurationSetResponse]
ReadPrec CreateConfigurationSetResponse
Int -> ReadS CreateConfigurationSetResponse
ReadS [CreateConfigurationSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateConfigurationSetResponse]
$creadListPrec :: ReadPrec [CreateConfigurationSetResponse]
readPrec :: ReadPrec CreateConfigurationSetResponse
$creadPrec :: ReadPrec CreateConfigurationSetResponse
readList :: ReadS [CreateConfigurationSetResponse]
$creadList :: ReadS [CreateConfigurationSetResponse]
readsPrec :: Int -> ReadS CreateConfigurationSetResponse
$creadsPrec :: Int -> ReadS CreateConfigurationSetResponse
Prelude.Read, Int -> CreateConfigurationSetResponse -> ShowS
[CreateConfigurationSetResponse] -> ShowS
CreateConfigurationSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConfigurationSetResponse] -> ShowS
$cshowList :: [CreateConfigurationSetResponse] -> ShowS
show :: CreateConfigurationSetResponse -> String
$cshow :: CreateConfigurationSetResponse -> String
showsPrec :: Int -> CreateConfigurationSetResponse -> ShowS
$cshowsPrec :: Int -> CreateConfigurationSetResponse -> ShowS
Prelude.Show, forall x.
Rep CreateConfigurationSetResponse x
-> CreateConfigurationSetResponse
forall x.
CreateConfigurationSetResponse
-> Rep CreateConfigurationSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateConfigurationSetResponse x
-> CreateConfigurationSetResponse
$cfrom :: forall x.
CreateConfigurationSetResponse
-> Rep CreateConfigurationSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateConfigurationSetResponse' 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', 'createConfigurationSetResponse_httpStatus' - The response's http status code.
newCreateConfigurationSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateConfigurationSetResponse
newCreateConfigurationSetResponse :: Int -> CreateConfigurationSetResponse
newCreateConfigurationSetResponse Int
pHttpStatus_ =
  CreateConfigurationSetResponse'
    { $sel:httpStatus:CreateConfigurationSetResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    CreateConfigurationSetResponse
  where
  rnf :: CreateConfigurationSetResponse -> ()
rnf CreateConfigurationSetResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateConfigurationSetResponse' :: CreateConfigurationSetResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus