{-# 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.SMS.DeleteServerCatalog
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes all servers from your server catalog.
module Amazonka.SMS.DeleteServerCatalog
  ( -- * Creating a Request
    DeleteServerCatalog (..),
    newDeleteServerCatalog,

    -- * Destructuring the Response
    DeleteServerCatalogResponse (..),
    newDeleteServerCatalogResponse,

    -- * Response Lenses
    deleteServerCatalogResponse_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.SMS.Types

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

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

instance Core.AWSRequest DeleteServerCatalog where
  type
    AWSResponse DeleteServerCatalog =
      DeleteServerCatalogResponse
  request :: (Service -> Service)
-> DeleteServerCatalog -> Request DeleteServerCatalog
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 DeleteServerCatalog
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteServerCatalog)))
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 -> DeleteServerCatalogResponse
DeleteServerCatalogResponse'
            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 DeleteServerCatalog where
  hashWithSalt :: Int -> DeleteServerCatalog -> Int
hashWithSalt Int
_salt DeleteServerCatalog
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders DeleteServerCatalog where
  toHeaders :: DeleteServerCatalog -> 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
"AWSServerMigrationService_V2016_10_24.DeleteServerCatalog" ::
                          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 DeleteServerCatalog where
  toJSON :: DeleteServerCatalog -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

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

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

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