{-# 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.SmsVoice.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 new configuration set. After you create the configuration set,
-- you can add one or more event destinations to it.
module Amazonka.SmsVoice.CreateConfigurationSet
  ( -- * Creating a Request
    CreateConfigurationSet (..),
    newCreateConfigurationSet,

    -- * Request Lenses
    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 qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SmsVoice.Types

-- | A request to create a new configuration set.
--
-- /See:/ 'newCreateConfigurationSet' smart constructor.
data CreateConfigurationSet = CreateConfigurationSet'
  { -- | The name that you want to give the configuration set.
    CreateConfigurationSet -> Maybe Text
configurationSetName :: Prelude.Maybe 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:
--
-- 'configurationSetName', 'createConfigurationSet_configurationSetName' - The name that you want to give the configuration set.
newCreateConfigurationSet ::
  CreateConfigurationSet
newCreateConfigurationSet :: CreateConfigurationSet
newCreateConfigurationSet =
  CreateConfigurationSet'
    { $sel:configurationSetName:CreateConfigurationSet' :: Maybe Text
configurationSetName =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The name that you want to give the configuration set.
createConfigurationSet_configurationSetName :: Lens.Lens' CreateConfigurationSet (Prelude.Maybe Prelude.Text)
createConfigurationSet_configurationSetName :: Lens' CreateConfigurationSet (Maybe Text)
createConfigurationSet_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationSet' {Maybe Text
configurationSetName :: Maybe Text
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe Text
configurationSetName} -> Maybe Text
configurationSetName) (\s :: CreateConfigurationSet
s@CreateConfigurationSet' {} Maybe Text
a -> CreateConfigurationSet
s {$sel:configurationSetName:CreateConfigurationSet' :: Maybe Text
configurationSetName = Maybe 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 Text
configurationSetName :: Maybe Text
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
configurationSetName

instance Prelude.NFData CreateConfigurationSet where
  rnf :: CreateConfigurationSet -> ()
rnf CreateConfigurationSet' {Maybe Text
configurationSetName :: Maybe Text
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe 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 Text
configurationSetName :: Maybe Text
$sel:configurationSetName:CreateConfigurationSet' :: CreateConfigurationSet -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConfigurationSetName" 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
configurationSetName
          ]
      )

instance Data.ToPath CreateConfigurationSet where
  toPath :: CreateConfigurationSet -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/v1/sms-voice/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 empty object that indicates that the configuration set was
-- successfully created.
--
-- /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