{-# 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.DirectoryService.DeleteConditionalForwarder
-- 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 a conditional forwarder that has been set up for your Amazon Web
-- Services directory.
module Amazonka.DirectoryService.DeleteConditionalForwarder
  ( -- * Creating a Request
    DeleteConditionalForwarder (..),
    newDeleteConditionalForwarder,

    -- * Request Lenses
    deleteConditionalForwarder_directoryId,
    deleteConditionalForwarder_remoteDomainName,

    -- * Destructuring the Response
    DeleteConditionalForwarderResponse (..),
    newDeleteConditionalForwarderResponse,

    -- * Response Lenses
    deleteConditionalForwarderResponse_httpStatus,
  )
where

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

-- | Deletes a conditional forwarder.
--
-- /See:/ 'newDeleteConditionalForwarder' smart constructor.
data DeleteConditionalForwarder = DeleteConditionalForwarder'
  { -- | The directory ID for which you are deleting the conditional forwarder.
    DeleteConditionalForwarder -> Text
directoryId :: Prelude.Text,
    -- | The fully qualified domain name (FQDN) of the remote domain with which
    -- you are deleting the conditional forwarder.
    DeleteConditionalForwarder -> Text
remoteDomainName :: Prelude.Text
  }
  deriving (DeleteConditionalForwarder -> DeleteConditionalForwarder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteConditionalForwarder -> DeleteConditionalForwarder -> Bool
$c/= :: DeleteConditionalForwarder -> DeleteConditionalForwarder -> Bool
== :: DeleteConditionalForwarder -> DeleteConditionalForwarder -> Bool
$c== :: DeleteConditionalForwarder -> DeleteConditionalForwarder -> Bool
Prelude.Eq, ReadPrec [DeleteConditionalForwarder]
ReadPrec DeleteConditionalForwarder
Int -> ReadS DeleteConditionalForwarder
ReadS [DeleteConditionalForwarder]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteConditionalForwarder]
$creadListPrec :: ReadPrec [DeleteConditionalForwarder]
readPrec :: ReadPrec DeleteConditionalForwarder
$creadPrec :: ReadPrec DeleteConditionalForwarder
readList :: ReadS [DeleteConditionalForwarder]
$creadList :: ReadS [DeleteConditionalForwarder]
readsPrec :: Int -> ReadS DeleteConditionalForwarder
$creadsPrec :: Int -> ReadS DeleteConditionalForwarder
Prelude.Read, Int -> DeleteConditionalForwarder -> ShowS
[DeleteConditionalForwarder] -> ShowS
DeleteConditionalForwarder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteConditionalForwarder] -> ShowS
$cshowList :: [DeleteConditionalForwarder] -> ShowS
show :: DeleteConditionalForwarder -> String
$cshow :: DeleteConditionalForwarder -> String
showsPrec :: Int -> DeleteConditionalForwarder -> ShowS
$cshowsPrec :: Int -> DeleteConditionalForwarder -> ShowS
Prelude.Show, forall x.
Rep DeleteConditionalForwarder x -> DeleteConditionalForwarder
forall x.
DeleteConditionalForwarder -> Rep DeleteConditionalForwarder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteConditionalForwarder x -> DeleteConditionalForwarder
$cfrom :: forall x.
DeleteConditionalForwarder -> Rep DeleteConditionalForwarder x
Prelude.Generic)

-- |
-- Create a value of 'DeleteConditionalForwarder' 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:
--
-- 'directoryId', 'deleteConditionalForwarder_directoryId' - The directory ID for which you are deleting the conditional forwarder.
--
-- 'remoteDomainName', 'deleteConditionalForwarder_remoteDomainName' - The fully qualified domain name (FQDN) of the remote domain with which
-- you are deleting the conditional forwarder.
newDeleteConditionalForwarder ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'remoteDomainName'
  Prelude.Text ->
  DeleteConditionalForwarder
newDeleteConditionalForwarder :: Text -> Text -> DeleteConditionalForwarder
newDeleteConditionalForwarder
  Text
pDirectoryId_
  Text
pRemoteDomainName_ =
    DeleteConditionalForwarder'
      { $sel:directoryId:DeleteConditionalForwarder' :: Text
directoryId =
          Text
pDirectoryId_,
        $sel:remoteDomainName:DeleteConditionalForwarder' :: Text
remoteDomainName = Text
pRemoteDomainName_
      }

-- | The directory ID for which you are deleting the conditional forwarder.
deleteConditionalForwarder_directoryId :: Lens.Lens' DeleteConditionalForwarder Prelude.Text
deleteConditionalForwarder_directoryId :: Lens' DeleteConditionalForwarder Text
deleteConditionalForwarder_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConditionalForwarder' {Text
directoryId :: Text
$sel:directoryId:DeleteConditionalForwarder' :: DeleteConditionalForwarder -> Text
directoryId} -> Text
directoryId) (\s :: DeleteConditionalForwarder
s@DeleteConditionalForwarder' {} Text
a -> DeleteConditionalForwarder
s {$sel:directoryId:DeleteConditionalForwarder' :: Text
directoryId = Text
a} :: DeleteConditionalForwarder)

-- | The fully qualified domain name (FQDN) of the remote domain with which
-- you are deleting the conditional forwarder.
deleteConditionalForwarder_remoteDomainName :: Lens.Lens' DeleteConditionalForwarder Prelude.Text
deleteConditionalForwarder_remoteDomainName :: Lens' DeleteConditionalForwarder Text
deleteConditionalForwarder_remoteDomainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteConditionalForwarder' {Text
remoteDomainName :: Text
$sel:remoteDomainName:DeleteConditionalForwarder' :: DeleteConditionalForwarder -> Text
remoteDomainName} -> Text
remoteDomainName) (\s :: DeleteConditionalForwarder
s@DeleteConditionalForwarder' {} Text
a -> DeleteConditionalForwarder
s {$sel:remoteDomainName:DeleteConditionalForwarder' :: Text
remoteDomainName = Text
a} :: DeleteConditionalForwarder)

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

instance Prelude.NFData DeleteConditionalForwarder where
  rnf :: DeleteConditionalForwarder -> ()
rnf DeleteConditionalForwarder' {Text
remoteDomainName :: Text
directoryId :: Text
$sel:remoteDomainName:DeleteConditionalForwarder' :: DeleteConditionalForwarder -> Text
$sel:directoryId:DeleteConditionalForwarder' :: DeleteConditionalForwarder -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
remoteDomainName

instance Data.ToHeaders DeleteConditionalForwarder where
  toHeaders :: DeleteConditionalForwarder -> 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
"DirectoryService_20150416.DeleteConditionalForwarder" ::
                          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 DeleteConditionalForwarder where
  toJSON :: DeleteConditionalForwarder -> Value
toJSON DeleteConditionalForwarder' {Text
remoteDomainName :: Text
directoryId :: Text
$sel:remoteDomainName:DeleteConditionalForwarder' :: DeleteConditionalForwarder -> Text
$sel:directoryId:DeleteConditionalForwarder' :: DeleteConditionalForwarder -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"DirectoryId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
directoryId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"RemoteDomainName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
remoteDomainName)
          ]
      )

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

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

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

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

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

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