{-# 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.GameLift.DeleteMatchmakingConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Permanently removes a FlexMatch matchmaking configuration. To delete,
-- specify the configuration name. A matchmaking configuration cannot be
-- deleted if it is being used in any active matchmaking tickets.
module Amazonka.GameLift.DeleteMatchmakingConfiguration
  ( -- * Creating a Request
    DeleteMatchmakingConfiguration (..),
    newDeleteMatchmakingConfiguration,

    -- * Request Lenses
    deleteMatchmakingConfiguration_name,

    -- * Destructuring the Response
    DeleteMatchmakingConfigurationResponse (..),
    newDeleteMatchmakingConfigurationResponse,

    -- * Response Lenses
    deleteMatchmakingConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteMatchmakingConfiguration' smart constructor.
data DeleteMatchmakingConfiguration = DeleteMatchmakingConfiguration'
  { -- | A unique identifier for the matchmaking configuration. You can use
    -- either the configuration name or ARN value.
    DeleteMatchmakingConfiguration -> Text
name :: Prelude.Text
  }
  deriving (DeleteMatchmakingConfiguration
-> DeleteMatchmakingConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteMatchmakingConfiguration
-> DeleteMatchmakingConfiguration -> Bool
$c/= :: DeleteMatchmakingConfiguration
-> DeleteMatchmakingConfiguration -> Bool
== :: DeleteMatchmakingConfiguration
-> DeleteMatchmakingConfiguration -> Bool
$c== :: DeleteMatchmakingConfiguration
-> DeleteMatchmakingConfiguration -> Bool
Prelude.Eq, ReadPrec [DeleteMatchmakingConfiguration]
ReadPrec DeleteMatchmakingConfiguration
Int -> ReadS DeleteMatchmakingConfiguration
ReadS [DeleteMatchmakingConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteMatchmakingConfiguration]
$creadListPrec :: ReadPrec [DeleteMatchmakingConfiguration]
readPrec :: ReadPrec DeleteMatchmakingConfiguration
$creadPrec :: ReadPrec DeleteMatchmakingConfiguration
readList :: ReadS [DeleteMatchmakingConfiguration]
$creadList :: ReadS [DeleteMatchmakingConfiguration]
readsPrec :: Int -> ReadS DeleteMatchmakingConfiguration
$creadsPrec :: Int -> ReadS DeleteMatchmakingConfiguration
Prelude.Read, Int -> DeleteMatchmakingConfiguration -> ShowS
[DeleteMatchmakingConfiguration] -> ShowS
DeleteMatchmakingConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteMatchmakingConfiguration] -> ShowS
$cshowList :: [DeleteMatchmakingConfiguration] -> ShowS
show :: DeleteMatchmakingConfiguration -> String
$cshow :: DeleteMatchmakingConfiguration -> String
showsPrec :: Int -> DeleteMatchmakingConfiguration -> ShowS
$cshowsPrec :: Int -> DeleteMatchmakingConfiguration -> ShowS
Prelude.Show, forall x.
Rep DeleteMatchmakingConfiguration x
-> DeleteMatchmakingConfiguration
forall x.
DeleteMatchmakingConfiguration
-> Rep DeleteMatchmakingConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteMatchmakingConfiguration x
-> DeleteMatchmakingConfiguration
$cfrom :: forall x.
DeleteMatchmakingConfiguration
-> Rep DeleteMatchmakingConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DeleteMatchmakingConfiguration' 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:
--
-- 'name', 'deleteMatchmakingConfiguration_name' - A unique identifier for the matchmaking configuration. You can use
-- either the configuration name or ARN value.
newDeleteMatchmakingConfiguration ::
  -- | 'name'
  Prelude.Text ->
  DeleteMatchmakingConfiguration
newDeleteMatchmakingConfiguration :: Text -> DeleteMatchmakingConfiguration
newDeleteMatchmakingConfiguration Text
pName_ =
  DeleteMatchmakingConfiguration' {$sel:name:DeleteMatchmakingConfiguration' :: Text
name = Text
pName_}

-- | A unique identifier for the matchmaking configuration. You can use
-- either the configuration name or ARN value.
deleteMatchmakingConfiguration_name :: Lens.Lens' DeleteMatchmakingConfiguration Prelude.Text
deleteMatchmakingConfiguration_name :: Lens' DeleteMatchmakingConfiguration Text
deleteMatchmakingConfiguration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteMatchmakingConfiguration' {Text
name :: Text
$sel:name:DeleteMatchmakingConfiguration' :: DeleteMatchmakingConfiguration -> Text
name} -> Text
name) (\s :: DeleteMatchmakingConfiguration
s@DeleteMatchmakingConfiguration' {} Text
a -> DeleteMatchmakingConfiguration
s {$sel:name:DeleteMatchmakingConfiguration' :: Text
name = Text
a} :: DeleteMatchmakingConfiguration)

instance
  Core.AWSRequest
    DeleteMatchmakingConfiguration
  where
  type
    AWSResponse DeleteMatchmakingConfiguration =
      DeleteMatchmakingConfigurationResponse
  request :: (Service -> Service)
-> DeleteMatchmakingConfiguration
-> Request DeleteMatchmakingConfiguration
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 DeleteMatchmakingConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteMatchmakingConfiguration)))
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 -> DeleteMatchmakingConfigurationResponse
DeleteMatchmakingConfigurationResponse'
            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
    DeleteMatchmakingConfiguration
  where
  hashWithSalt :: Int -> DeleteMatchmakingConfiguration -> Int
hashWithSalt
    Int
_salt
    DeleteMatchmakingConfiguration' {Text
name :: Text
$sel:name:DeleteMatchmakingConfiguration' :: DeleteMatchmakingConfiguration -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance
  Prelude.NFData
    DeleteMatchmakingConfiguration
  where
  rnf :: DeleteMatchmakingConfiguration -> ()
rnf DeleteMatchmakingConfiguration' {Text
name :: Text
$sel:name:DeleteMatchmakingConfiguration' :: DeleteMatchmakingConfiguration -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance
  Data.ToHeaders
    DeleteMatchmakingConfiguration
  where
  toHeaders :: DeleteMatchmakingConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"GameLift.DeleteMatchmakingConfiguration" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteMatchmakingConfiguration where
  toJSON :: DeleteMatchmakingConfiguration -> Value
toJSON DeleteMatchmakingConfiguration' {Text
name :: Text
$sel:name:DeleteMatchmakingConfiguration' :: DeleteMatchmakingConfiguration -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

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

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

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

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

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

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