{-# 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.CreateConditionalForwarder
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a conditional forwarder associated with your Amazon Web Services
-- directory. Conditional forwarders are required in order to set up a
-- trust relationship with another domain. The conditional forwarder points
-- to the trusted domain.
module Amazonka.DirectoryService.CreateConditionalForwarder
  ( -- * Creating a Request
    CreateConditionalForwarder (..),
    newCreateConditionalForwarder,

    -- * Request Lenses
    createConditionalForwarder_directoryId,
    createConditionalForwarder_remoteDomainName,
    createConditionalForwarder_dnsIpAddrs,

    -- * Destructuring the Response
    CreateConditionalForwarderResponse (..),
    newCreateConditionalForwarderResponse,

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

-- | Initiates the creation of a conditional forwarder for your Directory
-- Service for Microsoft Active Directory. Conditional forwarders are
-- required in order to set up a trust relationship with another domain.
--
-- /See:/ 'newCreateConditionalForwarder' smart constructor.
data CreateConditionalForwarder = CreateConditionalForwarder'
  { -- | The directory ID of the Amazon Web Services directory for which you are
    -- creating the conditional forwarder.
    CreateConditionalForwarder -> Text
directoryId :: Prelude.Text,
    -- | The fully qualified domain name (FQDN) of the remote domain with which
    -- you will set up a trust relationship.
    CreateConditionalForwarder -> Text
remoteDomainName :: Prelude.Text,
    -- | The IP addresses of the remote DNS server associated with
    -- RemoteDomainName.
    CreateConditionalForwarder -> [Text]
dnsIpAddrs :: [Prelude.Text]
  }
  deriving (CreateConditionalForwarder -> CreateConditionalForwarder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConditionalForwarder -> CreateConditionalForwarder -> Bool
$c/= :: CreateConditionalForwarder -> CreateConditionalForwarder -> Bool
== :: CreateConditionalForwarder -> CreateConditionalForwarder -> Bool
$c== :: CreateConditionalForwarder -> CreateConditionalForwarder -> Bool
Prelude.Eq, ReadPrec [CreateConditionalForwarder]
ReadPrec CreateConditionalForwarder
Int -> ReadS CreateConditionalForwarder
ReadS [CreateConditionalForwarder]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateConditionalForwarder]
$creadListPrec :: ReadPrec [CreateConditionalForwarder]
readPrec :: ReadPrec CreateConditionalForwarder
$creadPrec :: ReadPrec CreateConditionalForwarder
readList :: ReadS [CreateConditionalForwarder]
$creadList :: ReadS [CreateConditionalForwarder]
readsPrec :: Int -> ReadS CreateConditionalForwarder
$creadsPrec :: Int -> ReadS CreateConditionalForwarder
Prelude.Read, Int -> CreateConditionalForwarder -> ShowS
[CreateConditionalForwarder] -> ShowS
CreateConditionalForwarder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConditionalForwarder] -> ShowS
$cshowList :: [CreateConditionalForwarder] -> ShowS
show :: CreateConditionalForwarder -> String
$cshow :: CreateConditionalForwarder -> String
showsPrec :: Int -> CreateConditionalForwarder -> ShowS
$cshowsPrec :: Int -> CreateConditionalForwarder -> ShowS
Prelude.Show, forall x.
Rep CreateConditionalForwarder x -> CreateConditionalForwarder
forall x.
CreateConditionalForwarder -> Rep CreateConditionalForwarder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateConditionalForwarder x -> CreateConditionalForwarder
$cfrom :: forall x.
CreateConditionalForwarder -> Rep CreateConditionalForwarder x
Prelude.Generic)

-- |
-- Create a value of 'CreateConditionalForwarder' 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', 'createConditionalForwarder_directoryId' - The directory ID of the Amazon Web Services directory for which you are
-- creating the conditional forwarder.
--
-- 'remoteDomainName', 'createConditionalForwarder_remoteDomainName' - The fully qualified domain name (FQDN) of the remote domain with which
-- you will set up a trust relationship.
--
-- 'dnsIpAddrs', 'createConditionalForwarder_dnsIpAddrs' - The IP addresses of the remote DNS server associated with
-- RemoteDomainName.
newCreateConditionalForwarder ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'remoteDomainName'
  Prelude.Text ->
  CreateConditionalForwarder
newCreateConditionalForwarder :: Text -> Text -> CreateConditionalForwarder
newCreateConditionalForwarder
  Text
pDirectoryId_
  Text
pRemoteDomainName_ =
    CreateConditionalForwarder'
      { $sel:directoryId:CreateConditionalForwarder' :: Text
directoryId =
          Text
pDirectoryId_,
        $sel:remoteDomainName:CreateConditionalForwarder' :: Text
remoteDomainName = Text
pRemoteDomainName_,
        $sel:dnsIpAddrs:CreateConditionalForwarder' :: [Text]
dnsIpAddrs = forall a. Monoid a => a
Prelude.mempty
      }

-- | The directory ID of the Amazon Web Services directory for which you are
-- creating the conditional forwarder.
createConditionalForwarder_directoryId :: Lens.Lens' CreateConditionalForwarder Prelude.Text
createConditionalForwarder_directoryId :: Lens' CreateConditionalForwarder Text
createConditionalForwarder_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConditionalForwarder' {Text
directoryId :: Text
$sel:directoryId:CreateConditionalForwarder' :: CreateConditionalForwarder -> Text
directoryId} -> Text
directoryId) (\s :: CreateConditionalForwarder
s@CreateConditionalForwarder' {} Text
a -> CreateConditionalForwarder
s {$sel:directoryId:CreateConditionalForwarder' :: Text
directoryId = Text
a} :: CreateConditionalForwarder)

-- | The fully qualified domain name (FQDN) of the remote domain with which
-- you will set up a trust relationship.
createConditionalForwarder_remoteDomainName :: Lens.Lens' CreateConditionalForwarder Prelude.Text
createConditionalForwarder_remoteDomainName :: Lens' CreateConditionalForwarder Text
createConditionalForwarder_remoteDomainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConditionalForwarder' {Text
remoteDomainName :: Text
$sel:remoteDomainName:CreateConditionalForwarder' :: CreateConditionalForwarder -> Text
remoteDomainName} -> Text
remoteDomainName) (\s :: CreateConditionalForwarder
s@CreateConditionalForwarder' {} Text
a -> CreateConditionalForwarder
s {$sel:remoteDomainName:CreateConditionalForwarder' :: Text
remoteDomainName = Text
a} :: CreateConditionalForwarder)

-- | The IP addresses of the remote DNS server associated with
-- RemoteDomainName.
createConditionalForwarder_dnsIpAddrs :: Lens.Lens' CreateConditionalForwarder [Prelude.Text]
createConditionalForwarder_dnsIpAddrs :: Lens' CreateConditionalForwarder [Text]
createConditionalForwarder_dnsIpAddrs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConditionalForwarder' {[Text]
dnsIpAddrs :: [Text]
$sel:dnsIpAddrs:CreateConditionalForwarder' :: CreateConditionalForwarder -> [Text]
dnsIpAddrs} -> [Text]
dnsIpAddrs) (\s :: CreateConditionalForwarder
s@CreateConditionalForwarder' {} [Text]
a -> CreateConditionalForwarder
s {$sel:dnsIpAddrs:CreateConditionalForwarder' :: [Text]
dnsIpAddrs = [Text]
a} :: CreateConditionalForwarder) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData CreateConditionalForwarder where
  rnf :: CreateConditionalForwarder -> ()
rnf CreateConditionalForwarder' {[Text]
Text
dnsIpAddrs :: [Text]
remoteDomainName :: Text
directoryId :: Text
$sel:dnsIpAddrs:CreateConditionalForwarder' :: CreateConditionalForwarder -> [Text]
$sel:remoteDomainName:CreateConditionalForwarder' :: CreateConditionalForwarder -> Text
$sel:directoryId:CreateConditionalForwarder' :: CreateConditionalForwarder -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
dnsIpAddrs

instance Data.ToHeaders CreateConditionalForwarder where
  toHeaders :: CreateConditionalForwarder -> 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.CreateConditionalForwarder" ::
                          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 CreateConditionalForwarder where
  toJSON :: CreateConditionalForwarder -> Value
toJSON CreateConditionalForwarder' {[Text]
Text
dnsIpAddrs :: [Text]
remoteDomainName :: Text
directoryId :: Text
$sel:dnsIpAddrs:CreateConditionalForwarder' :: CreateConditionalForwarder -> [Text]
$sel:remoteDomainName:CreateConditionalForwarder' :: CreateConditionalForwarder -> Text
$sel:directoryId:CreateConditionalForwarder' :: CreateConditionalForwarder -> 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),
            forall a. a -> Maybe a
Prelude.Just (Key
"DnsIpAddrs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
dnsIpAddrs)
          ]
      )

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

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

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

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

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

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