{-# 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.MediaConvert.DeletePreset
-- 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 delete a preset you have created.
module Amazonka.MediaConvert.DeletePreset
  ( -- * Creating a Request
    DeletePreset (..),
    newDeletePreset,

    -- * Request Lenses
    deletePreset_name,

    -- * Destructuring the Response
    DeletePresetResponse (..),
    newDeletePresetResponse,

    -- * Response Lenses
    deletePresetResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeletePreset' 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', 'deletePreset_name' - The name of the preset to be deleted.
newDeletePreset ::
  -- | 'name'
  Prelude.Text ->
  DeletePreset
newDeletePreset :: Text -> DeletePreset
newDeletePreset Text
pName_ = DeletePreset' {$sel:name:DeletePreset' :: Text
name = Text
pName_}

-- | The name of the preset to be deleted.
deletePreset_name :: Lens.Lens' DeletePreset Prelude.Text
deletePreset_name :: Lens' DeletePreset Text
deletePreset_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePreset' {Text
name :: Text
$sel:name:DeletePreset' :: DeletePreset -> Text
name} -> Text
name) (\s :: DeletePreset
s@DeletePreset' {} Text
a -> DeletePreset
s {$sel:name:DeletePreset' :: Text
name = Text
a} :: DeletePreset)

instance Core.AWSRequest DeletePreset where
  type AWSResponse DeletePreset = DeletePresetResponse
  request :: (Service -> Service) -> DeletePreset -> Request DeletePreset
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeletePreset
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeletePreset)))
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 -> DeletePresetResponse
DeletePresetResponse'
            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 DeletePreset where
  hashWithSalt :: Int -> DeletePreset -> Int
hashWithSalt Int
_salt DeletePreset' {Text
name :: Text
$sel:name:DeletePreset' :: DeletePreset -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders DeletePreset where
  toHeaders :: DeletePreset -> 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.ToPath DeletePreset where
  toPath :: DeletePreset -> ByteString
toPath DeletePreset' {Text
name :: Text
$sel:name:DeletePreset' :: DeletePreset -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2017-08-29/presets/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

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

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

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

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