{-# 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.RemoveRegion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops all replication and removes the domain controllers from the
-- specified Region. You cannot remove the primary Region with this
-- operation. Instead, use the @DeleteDirectory@ API.
module Amazonka.DirectoryService.RemoveRegion
  ( -- * Creating a Request
    RemoveRegion (..),
    newRemoveRegion,

    -- * Request Lenses
    removeRegion_directoryId,

    -- * Destructuring the Response
    RemoveRegionResponse (..),
    newRemoveRegionResponse,

    -- * Response Lenses
    removeRegionResponse_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

-- | /See:/ 'newRemoveRegion' smart constructor.
data RemoveRegion = RemoveRegion'
  { -- | The identifier of the directory for which you want to remove Region
    -- replication.
    RemoveRegion -> Text
directoryId :: Prelude.Text
  }
  deriving (RemoveRegion -> RemoveRegion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveRegion -> RemoveRegion -> Bool
$c/= :: RemoveRegion -> RemoveRegion -> Bool
== :: RemoveRegion -> RemoveRegion -> Bool
$c== :: RemoveRegion -> RemoveRegion -> Bool
Prelude.Eq, ReadPrec [RemoveRegion]
ReadPrec RemoveRegion
Int -> ReadS RemoveRegion
ReadS [RemoveRegion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveRegion]
$creadListPrec :: ReadPrec [RemoveRegion]
readPrec :: ReadPrec RemoveRegion
$creadPrec :: ReadPrec RemoveRegion
readList :: ReadS [RemoveRegion]
$creadList :: ReadS [RemoveRegion]
readsPrec :: Int -> ReadS RemoveRegion
$creadsPrec :: Int -> ReadS RemoveRegion
Prelude.Read, Int -> RemoveRegion -> ShowS
[RemoveRegion] -> ShowS
RemoveRegion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveRegion] -> ShowS
$cshowList :: [RemoveRegion] -> ShowS
show :: RemoveRegion -> String
$cshow :: RemoveRegion -> String
showsPrec :: Int -> RemoveRegion -> ShowS
$cshowsPrec :: Int -> RemoveRegion -> ShowS
Prelude.Show, forall x. Rep RemoveRegion x -> RemoveRegion
forall x. RemoveRegion -> Rep RemoveRegion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveRegion x -> RemoveRegion
$cfrom :: forall x. RemoveRegion -> Rep RemoveRegion x
Prelude.Generic)

-- |
-- Create a value of 'RemoveRegion' 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', 'removeRegion_directoryId' - The identifier of the directory for which you want to remove Region
-- replication.
newRemoveRegion ::
  -- | 'directoryId'
  Prelude.Text ->
  RemoveRegion
newRemoveRegion :: Text -> RemoveRegion
newRemoveRegion Text
pDirectoryId_ =
  RemoveRegion' {$sel:directoryId:RemoveRegion' :: Text
directoryId = Text
pDirectoryId_}

-- | The identifier of the directory for which you want to remove Region
-- replication.
removeRegion_directoryId :: Lens.Lens' RemoveRegion Prelude.Text
removeRegion_directoryId :: Lens' RemoveRegion Text
removeRegion_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveRegion' {Text
directoryId :: Text
$sel:directoryId:RemoveRegion' :: RemoveRegion -> Text
directoryId} -> Text
directoryId) (\s :: RemoveRegion
s@RemoveRegion' {} Text
a -> RemoveRegion
s {$sel:directoryId:RemoveRegion' :: Text
directoryId = Text
a} :: RemoveRegion)

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

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

instance Data.ToHeaders RemoveRegion where
  toHeaders :: RemoveRegion -> 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.RemoveRegion" ::
                          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 RemoveRegion where
  toJSON :: RemoveRegion -> Value
toJSON RemoveRegion' {Text
directoryId :: Text
$sel:directoryId:RemoveRegion' :: RemoveRegion -> 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)]
      )

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

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

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

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

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

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