{-# 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.DescribeConditionalForwarders
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Obtains information about the conditional forwarders for this account.
--
-- If no input parameters are provided for RemoteDomainNames, this request
-- describes all conditional forwarders for the specified directory ID.
module Amazonka.DirectoryService.DescribeConditionalForwarders
  ( -- * Creating a Request
    DescribeConditionalForwarders (..),
    newDescribeConditionalForwarders,

    -- * Request Lenses
    describeConditionalForwarders_remoteDomainNames,
    describeConditionalForwarders_directoryId,

    -- * Destructuring the Response
    DescribeConditionalForwardersResponse (..),
    newDescribeConditionalForwardersResponse,

    -- * Response Lenses
    describeConditionalForwardersResponse_conditionalForwarders,
    describeConditionalForwardersResponse_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

-- | Describes a conditional forwarder.
--
-- /See:/ 'newDescribeConditionalForwarders' smart constructor.
data DescribeConditionalForwarders = DescribeConditionalForwarders'
  { -- | The fully qualified domain names (FQDN) of the remote domains for which
    -- to get the list of associated conditional forwarders. If this member is
    -- null, all conditional forwarders are returned.
    DescribeConditionalForwarders -> Maybe [Text]
remoteDomainNames :: Prelude.Maybe [Prelude.Text],
    -- | The directory ID for which to get the list of associated conditional
    -- forwarders.
    DescribeConditionalForwarders -> Text
directoryId :: Prelude.Text
  }
  deriving (DescribeConditionalForwarders
-> DescribeConditionalForwarders -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConditionalForwarders
-> DescribeConditionalForwarders -> Bool
$c/= :: DescribeConditionalForwarders
-> DescribeConditionalForwarders -> Bool
== :: DescribeConditionalForwarders
-> DescribeConditionalForwarders -> Bool
$c== :: DescribeConditionalForwarders
-> DescribeConditionalForwarders -> Bool
Prelude.Eq, ReadPrec [DescribeConditionalForwarders]
ReadPrec DescribeConditionalForwarders
Int -> ReadS DescribeConditionalForwarders
ReadS [DescribeConditionalForwarders]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConditionalForwarders]
$creadListPrec :: ReadPrec [DescribeConditionalForwarders]
readPrec :: ReadPrec DescribeConditionalForwarders
$creadPrec :: ReadPrec DescribeConditionalForwarders
readList :: ReadS [DescribeConditionalForwarders]
$creadList :: ReadS [DescribeConditionalForwarders]
readsPrec :: Int -> ReadS DescribeConditionalForwarders
$creadsPrec :: Int -> ReadS DescribeConditionalForwarders
Prelude.Read, Int -> DescribeConditionalForwarders -> ShowS
[DescribeConditionalForwarders] -> ShowS
DescribeConditionalForwarders -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConditionalForwarders] -> ShowS
$cshowList :: [DescribeConditionalForwarders] -> ShowS
show :: DescribeConditionalForwarders -> String
$cshow :: DescribeConditionalForwarders -> String
showsPrec :: Int -> DescribeConditionalForwarders -> ShowS
$cshowsPrec :: Int -> DescribeConditionalForwarders -> ShowS
Prelude.Show, forall x.
Rep DescribeConditionalForwarders x
-> DescribeConditionalForwarders
forall x.
DescribeConditionalForwarders
-> Rep DescribeConditionalForwarders x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConditionalForwarders x
-> DescribeConditionalForwarders
$cfrom :: forall x.
DescribeConditionalForwarders
-> Rep DescribeConditionalForwarders x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConditionalForwarders' 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:
--
-- 'remoteDomainNames', 'describeConditionalForwarders_remoteDomainNames' - The fully qualified domain names (FQDN) of the remote domains for which
-- to get the list of associated conditional forwarders. If this member is
-- null, all conditional forwarders are returned.
--
-- 'directoryId', 'describeConditionalForwarders_directoryId' - The directory ID for which to get the list of associated conditional
-- forwarders.
newDescribeConditionalForwarders ::
  -- | 'directoryId'
  Prelude.Text ->
  DescribeConditionalForwarders
newDescribeConditionalForwarders :: Text -> DescribeConditionalForwarders
newDescribeConditionalForwarders Text
pDirectoryId_ =
  DescribeConditionalForwarders'
    { $sel:remoteDomainNames:DescribeConditionalForwarders' :: Maybe [Text]
remoteDomainNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:directoryId:DescribeConditionalForwarders' :: Text
directoryId = Text
pDirectoryId_
    }

-- | The fully qualified domain names (FQDN) of the remote domains for which
-- to get the list of associated conditional forwarders. If this member is
-- null, all conditional forwarders are returned.
describeConditionalForwarders_remoteDomainNames :: Lens.Lens' DescribeConditionalForwarders (Prelude.Maybe [Prelude.Text])
describeConditionalForwarders_remoteDomainNames :: Lens' DescribeConditionalForwarders (Maybe [Text])
describeConditionalForwarders_remoteDomainNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConditionalForwarders' {Maybe [Text]
remoteDomainNames :: Maybe [Text]
$sel:remoteDomainNames:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Maybe [Text]
remoteDomainNames} -> Maybe [Text]
remoteDomainNames) (\s :: DescribeConditionalForwarders
s@DescribeConditionalForwarders' {} Maybe [Text]
a -> DescribeConditionalForwarders
s {$sel:remoteDomainNames:DescribeConditionalForwarders' :: Maybe [Text]
remoteDomainNames = Maybe [Text]
a} :: DescribeConditionalForwarders) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The directory ID for which to get the list of associated conditional
-- forwarders.
describeConditionalForwarders_directoryId :: Lens.Lens' DescribeConditionalForwarders Prelude.Text
describeConditionalForwarders_directoryId :: Lens' DescribeConditionalForwarders Text
describeConditionalForwarders_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConditionalForwarders' {Text
directoryId :: Text
$sel:directoryId:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Text
directoryId} -> Text
directoryId) (\s :: DescribeConditionalForwarders
s@DescribeConditionalForwarders' {} Text
a -> DescribeConditionalForwarders
s {$sel:directoryId:DescribeConditionalForwarders' :: Text
directoryId = Text
a} :: DescribeConditionalForwarders)

instance
  Core.AWSRequest
    DescribeConditionalForwarders
  where
  type
    AWSResponse DescribeConditionalForwarders =
      DescribeConditionalForwardersResponse
  request :: (Service -> Service)
-> DescribeConditionalForwarders
-> Request DescribeConditionalForwarders
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 DescribeConditionalForwarders
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeConditionalForwarders)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [ConditionalForwarder]
-> Int -> DescribeConditionalForwardersResponse
DescribeConditionalForwardersResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ConditionalForwarders"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => 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
    DescribeConditionalForwarders
  where
  hashWithSalt :: Int -> DescribeConditionalForwarders -> Int
hashWithSalt Int
_salt DescribeConditionalForwarders' {Maybe [Text]
Text
directoryId :: Text
remoteDomainNames :: Maybe [Text]
$sel:directoryId:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Text
$sel:remoteDomainNames:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
remoteDomainNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId

instance Prelude.NFData DescribeConditionalForwarders where
  rnf :: DescribeConditionalForwarders -> ()
rnf DescribeConditionalForwarders' {Maybe [Text]
Text
directoryId :: Text
remoteDomainNames :: Maybe [Text]
$sel:directoryId:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Text
$sel:remoteDomainNames:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
remoteDomainNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId

instance Data.ToHeaders DescribeConditionalForwarders where
  toHeaders :: DescribeConditionalForwarders -> 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.DescribeConditionalForwarders" ::
                          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 DescribeConditionalForwarders where
  toJSON :: DescribeConditionalForwarders -> Value
toJSON DescribeConditionalForwarders' {Maybe [Text]
Text
directoryId :: Text
remoteDomainNames :: Maybe [Text]
$sel:directoryId:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Text
$sel:remoteDomainNames:DescribeConditionalForwarders' :: DescribeConditionalForwarders -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"RemoteDomainNames" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
remoteDomainNames,
            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 DescribeConditionalForwarders where
  toPath :: DescribeConditionalForwarders -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | The result of a DescribeConditionalForwarder request.
--
-- /See:/ 'newDescribeConditionalForwardersResponse' smart constructor.
data DescribeConditionalForwardersResponse = DescribeConditionalForwardersResponse'
  { -- | The list of conditional forwarders that have been created.
    DescribeConditionalForwardersResponse
-> Maybe [ConditionalForwarder]
conditionalForwarders :: Prelude.Maybe [ConditionalForwarder],
    -- | The response's http status code.
    DescribeConditionalForwardersResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeConditionalForwardersResponse
-> DescribeConditionalForwardersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConditionalForwardersResponse
-> DescribeConditionalForwardersResponse -> Bool
$c/= :: DescribeConditionalForwardersResponse
-> DescribeConditionalForwardersResponse -> Bool
== :: DescribeConditionalForwardersResponse
-> DescribeConditionalForwardersResponse -> Bool
$c== :: DescribeConditionalForwardersResponse
-> DescribeConditionalForwardersResponse -> Bool
Prelude.Eq, ReadPrec [DescribeConditionalForwardersResponse]
ReadPrec DescribeConditionalForwardersResponse
Int -> ReadS DescribeConditionalForwardersResponse
ReadS [DescribeConditionalForwardersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConditionalForwardersResponse]
$creadListPrec :: ReadPrec [DescribeConditionalForwardersResponse]
readPrec :: ReadPrec DescribeConditionalForwardersResponse
$creadPrec :: ReadPrec DescribeConditionalForwardersResponse
readList :: ReadS [DescribeConditionalForwardersResponse]
$creadList :: ReadS [DescribeConditionalForwardersResponse]
readsPrec :: Int -> ReadS DescribeConditionalForwardersResponse
$creadsPrec :: Int -> ReadS DescribeConditionalForwardersResponse
Prelude.Read, Int -> DescribeConditionalForwardersResponse -> ShowS
[DescribeConditionalForwardersResponse] -> ShowS
DescribeConditionalForwardersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConditionalForwardersResponse] -> ShowS
$cshowList :: [DescribeConditionalForwardersResponse] -> ShowS
show :: DescribeConditionalForwardersResponse -> String
$cshow :: DescribeConditionalForwardersResponse -> String
showsPrec :: Int -> DescribeConditionalForwardersResponse -> ShowS
$cshowsPrec :: Int -> DescribeConditionalForwardersResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeConditionalForwardersResponse x
-> DescribeConditionalForwardersResponse
forall x.
DescribeConditionalForwardersResponse
-> Rep DescribeConditionalForwardersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConditionalForwardersResponse x
-> DescribeConditionalForwardersResponse
$cfrom :: forall x.
DescribeConditionalForwardersResponse
-> Rep DescribeConditionalForwardersResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConditionalForwardersResponse' 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:
--
-- 'conditionalForwarders', 'describeConditionalForwardersResponse_conditionalForwarders' - The list of conditional forwarders that have been created.
--
-- 'httpStatus', 'describeConditionalForwardersResponse_httpStatus' - The response's http status code.
newDescribeConditionalForwardersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeConditionalForwardersResponse
newDescribeConditionalForwardersResponse :: Int -> DescribeConditionalForwardersResponse
newDescribeConditionalForwardersResponse Int
pHttpStatus_ =
  DescribeConditionalForwardersResponse'
    { $sel:conditionalForwarders:DescribeConditionalForwardersResponse' :: Maybe [ConditionalForwarder]
conditionalForwarders =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeConditionalForwardersResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of conditional forwarders that have been created.
describeConditionalForwardersResponse_conditionalForwarders :: Lens.Lens' DescribeConditionalForwardersResponse (Prelude.Maybe [ConditionalForwarder])
describeConditionalForwardersResponse_conditionalForwarders :: Lens'
  DescribeConditionalForwardersResponse
  (Maybe [ConditionalForwarder])
describeConditionalForwardersResponse_conditionalForwarders = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConditionalForwardersResponse' {Maybe [ConditionalForwarder]
conditionalForwarders :: Maybe [ConditionalForwarder]
$sel:conditionalForwarders:DescribeConditionalForwardersResponse' :: DescribeConditionalForwardersResponse
-> Maybe [ConditionalForwarder]
conditionalForwarders} -> Maybe [ConditionalForwarder]
conditionalForwarders) (\s :: DescribeConditionalForwardersResponse
s@DescribeConditionalForwardersResponse' {} Maybe [ConditionalForwarder]
a -> DescribeConditionalForwardersResponse
s {$sel:conditionalForwarders:DescribeConditionalForwardersResponse' :: Maybe [ConditionalForwarder]
conditionalForwarders = Maybe [ConditionalForwarder]
a} :: DescribeConditionalForwardersResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.NFData
    DescribeConditionalForwardersResponse
  where
  rnf :: DescribeConditionalForwardersResponse -> ()
rnf DescribeConditionalForwardersResponse' {Int
Maybe [ConditionalForwarder]
httpStatus :: Int
conditionalForwarders :: Maybe [ConditionalForwarder]
$sel:httpStatus:DescribeConditionalForwardersResponse' :: DescribeConditionalForwardersResponse -> Int
$sel:conditionalForwarders:DescribeConditionalForwardersResponse' :: DescribeConditionalForwardersResponse
-> Maybe [ConditionalForwarder]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ConditionalForwarder]
conditionalForwarders
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus