{-# 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.WorkMail.DeregisterMailDomain
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes a domain from WorkMail, stops email routing to WorkMail, and
-- removes the authorization allowing WorkMail use. SES keeps the domain
-- because other applications may use it. You must first remove any email
-- address used by WorkMail entities before you remove the domain.
module Amazonka.WorkMail.DeregisterMailDomain
  ( -- * Creating a Request
    DeregisterMailDomain (..),
    newDeregisterMailDomain,

    -- * Request Lenses
    deregisterMailDomain_organizationId,
    deregisterMailDomain_domainName,

    -- * Destructuring the Response
    DeregisterMailDomainResponse (..),
    newDeregisterMailDomainResponse,

    -- * Response Lenses
    deregisterMailDomainResponse_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.WorkMail.Types

-- | /See:/ 'newDeregisterMailDomain' smart constructor.
data DeregisterMailDomain = DeregisterMailDomain'
  { -- | The WorkMail organization for which the domain will be deregistered.
    DeregisterMailDomain -> Text
organizationId :: Prelude.Text,
    -- | The domain to deregister in WorkMail and SES.
    DeregisterMailDomain -> Text
domainName :: Prelude.Text
  }
  deriving (DeregisterMailDomain -> DeregisterMailDomain -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeregisterMailDomain -> DeregisterMailDomain -> Bool
$c/= :: DeregisterMailDomain -> DeregisterMailDomain -> Bool
== :: DeregisterMailDomain -> DeregisterMailDomain -> Bool
$c== :: DeregisterMailDomain -> DeregisterMailDomain -> Bool
Prelude.Eq, ReadPrec [DeregisterMailDomain]
ReadPrec DeregisterMailDomain
Int -> ReadS DeregisterMailDomain
ReadS [DeregisterMailDomain]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeregisterMailDomain]
$creadListPrec :: ReadPrec [DeregisterMailDomain]
readPrec :: ReadPrec DeregisterMailDomain
$creadPrec :: ReadPrec DeregisterMailDomain
readList :: ReadS [DeregisterMailDomain]
$creadList :: ReadS [DeregisterMailDomain]
readsPrec :: Int -> ReadS DeregisterMailDomain
$creadsPrec :: Int -> ReadS DeregisterMailDomain
Prelude.Read, Int -> DeregisterMailDomain -> ShowS
[DeregisterMailDomain] -> ShowS
DeregisterMailDomain -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeregisterMailDomain] -> ShowS
$cshowList :: [DeregisterMailDomain] -> ShowS
show :: DeregisterMailDomain -> String
$cshow :: DeregisterMailDomain -> String
showsPrec :: Int -> DeregisterMailDomain -> ShowS
$cshowsPrec :: Int -> DeregisterMailDomain -> ShowS
Prelude.Show, forall x. Rep DeregisterMailDomain x -> DeregisterMailDomain
forall x. DeregisterMailDomain -> Rep DeregisterMailDomain x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeregisterMailDomain x -> DeregisterMailDomain
$cfrom :: forall x. DeregisterMailDomain -> Rep DeregisterMailDomain x
Prelude.Generic)

-- |
-- Create a value of 'DeregisterMailDomain' 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:
--
-- 'organizationId', 'deregisterMailDomain_organizationId' - The WorkMail organization for which the domain will be deregistered.
--
-- 'domainName', 'deregisterMailDomain_domainName' - The domain to deregister in WorkMail and SES.
newDeregisterMailDomain ::
  -- | 'organizationId'
  Prelude.Text ->
  -- | 'domainName'
  Prelude.Text ->
  DeregisterMailDomain
newDeregisterMailDomain :: Text -> Text -> DeregisterMailDomain
newDeregisterMailDomain Text
pOrganizationId_ Text
pDomainName_ =
  DeregisterMailDomain'
    { $sel:organizationId:DeregisterMailDomain' :: Text
organizationId =
        Text
pOrganizationId_,
      $sel:domainName:DeregisterMailDomain' :: Text
domainName = Text
pDomainName_
    }

-- | The WorkMail organization for which the domain will be deregistered.
deregisterMailDomain_organizationId :: Lens.Lens' DeregisterMailDomain Prelude.Text
deregisterMailDomain_organizationId :: Lens' DeregisterMailDomain Text
deregisterMailDomain_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeregisterMailDomain' {Text
organizationId :: Text
$sel:organizationId:DeregisterMailDomain' :: DeregisterMailDomain -> Text
organizationId} -> Text
organizationId) (\s :: DeregisterMailDomain
s@DeregisterMailDomain' {} Text
a -> DeregisterMailDomain
s {$sel:organizationId:DeregisterMailDomain' :: Text
organizationId = Text
a} :: DeregisterMailDomain)

-- | The domain to deregister in WorkMail and SES.
deregisterMailDomain_domainName :: Lens.Lens' DeregisterMailDomain Prelude.Text
deregisterMailDomain_domainName :: Lens' DeregisterMailDomain Text
deregisterMailDomain_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeregisterMailDomain' {Text
domainName :: Text
$sel:domainName:DeregisterMailDomain' :: DeregisterMailDomain -> Text
domainName} -> Text
domainName) (\s :: DeregisterMailDomain
s@DeregisterMailDomain' {} Text
a -> DeregisterMailDomain
s {$sel:domainName:DeregisterMailDomain' :: Text
domainName = Text
a} :: DeregisterMailDomain)

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

instance Prelude.NFData DeregisterMailDomain where
  rnf :: DeregisterMailDomain -> ()
rnf DeregisterMailDomain' {Text
domainName :: Text
organizationId :: Text
$sel:domainName:DeregisterMailDomain' :: DeregisterMailDomain -> Text
$sel:organizationId:DeregisterMailDomain' :: DeregisterMailDomain -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName

instance Data.ToHeaders DeregisterMailDomain where
  toHeaders :: DeregisterMailDomain -> 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
"WorkMailService.DeregisterMailDomain" ::
                          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 DeregisterMailDomain where
  toJSON :: DeregisterMailDomain -> Value
toJSON DeregisterMailDomain' {Text
domainName :: Text
organizationId :: Text
$sel:domainName:DeregisterMailDomain' :: DeregisterMailDomain -> Text
$sel:organizationId:DeregisterMailDomain' :: DeregisterMailDomain -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId),
            forall a. a -> Maybe a
Prelude.Just (Key
"DomainName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domainName)
          ]
      )

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

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

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

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

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

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