{-# 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.ElasticSearch.DeleteElasticsearchServiceRole
-- 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 the service-linked role that Elasticsearch Service uses to
-- manage and maintain VPC domains. Role deletion will fail if any existing
-- VPC domains use the role. You must delete any such Elasticsearch domains
-- before deleting the role. See
-- <http://docs.aws.amazon.com/elasticsearch-service/latest/developerguide/es-vpc.html#es-enabling-slr Deleting Elasticsearch Service Role>
-- in /VPC Endpoints for Amazon Elasticsearch Service Domains/.
module Amazonka.ElasticSearch.DeleteElasticsearchServiceRole
  ( -- * Creating a Request
    DeleteElasticsearchServiceRole (..),
    newDeleteElasticsearchServiceRole,

    -- * Destructuring the Response
    DeleteElasticsearchServiceRoleResponse (..),
    newDeleteElasticsearchServiceRoleResponse,
  )
where

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

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

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

instance
  Core.AWSRequest
    DeleteElasticsearchServiceRole
  where
  type
    AWSResponse DeleteElasticsearchServiceRole =
      DeleteElasticsearchServiceRoleResponse
  request :: (Service -> Service)
-> DeleteElasticsearchServiceRole
-> Request DeleteElasticsearchServiceRole
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 DeleteElasticsearchServiceRole
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteElasticsearchServiceRole)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteElasticsearchServiceRoleResponse
DeleteElasticsearchServiceRoleResponse'

instance
  Prelude.Hashable
    DeleteElasticsearchServiceRole
  where
  hashWithSalt :: Int -> DeleteElasticsearchServiceRole -> Int
hashWithSalt Int
_salt DeleteElasticsearchServiceRole
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance
  Data.ToHeaders
    DeleteElasticsearchServiceRole
  where
  toHeaders :: DeleteElasticsearchServiceRole -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DeleteElasticsearchServiceRole where
  toPath :: DeleteElasticsearchServiceRole -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2015-01-01/es/role"

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

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

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

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