{-# 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.CloudSearch.DescribeDomains
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about the search domains owned by this account. Can be
-- limited to specific domains. Shows all domains by default. To get the
-- number of searchable documents in a domain, use the console or submit a
-- @matchall@ request to your domain\'s search endpoint:
-- @q=matchall&q.parser=structured&size=0@. For more information,
-- see
-- <http://docs.aws.amazon.com/cloudsearch/latest/developerguide/getting-domain-info.html Getting Information about a Search Domain>
-- in the /Amazon CloudSearch Developer Guide/.
module Amazonka.CloudSearch.DescribeDomains
  ( -- * Creating a Request
    DescribeDomains (..),
    newDescribeDomains,

    -- * Request Lenses
    describeDomains_domainNames,

    -- * Destructuring the Response
    DescribeDomainsResponse (..),
    newDescribeDomainsResponse,

    -- * Response Lenses
    describeDomainsResponse_httpStatus,
    describeDomainsResponse_domainStatusList,
  )
where

import Amazonka.CloudSearch.Types
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

-- | Container for the parameters to the @DescribeDomains@ operation. By
-- default shows the status of all domains. To restrict the response to
-- particular domains, specify the names of the domains you want to
-- describe.
--
-- /See:/ 'newDescribeDomains' smart constructor.
data DescribeDomains = DescribeDomains'
  { -- | The names of the domains you want to include in the response.
    DescribeDomains -> Maybe [Text]
domainNames :: Prelude.Maybe [Prelude.Text]
  }
  deriving (DescribeDomains -> DescribeDomains -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDomains -> DescribeDomains -> Bool
$c/= :: DescribeDomains -> DescribeDomains -> Bool
== :: DescribeDomains -> DescribeDomains -> Bool
$c== :: DescribeDomains -> DescribeDomains -> Bool
Prelude.Eq, ReadPrec [DescribeDomains]
ReadPrec DescribeDomains
Int -> ReadS DescribeDomains
ReadS [DescribeDomains]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDomains]
$creadListPrec :: ReadPrec [DescribeDomains]
readPrec :: ReadPrec DescribeDomains
$creadPrec :: ReadPrec DescribeDomains
readList :: ReadS [DescribeDomains]
$creadList :: ReadS [DescribeDomains]
readsPrec :: Int -> ReadS DescribeDomains
$creadsPrec :: Int -> ReadS DescribeDomains
Prelude.Read, Int -> DescribeDomains -> ShowS
[DescribeDomains] -> ShowS
DescribeDomains -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDomains] -> ShowS
$cshowList :: [DescribeDomains] -> ShowS
show :: DescribeDomains -> String
$cshow :: DescribeDomains -> String
showsPrec :: Int -> DescribeDomains -> ShowS
$cshowsPrec :: Int -> DescribeDomains -> ShowS
Prelude.Show, forall x. Rep DescribeDomains x -> DescribeDomains
forall x. DescribeDomains -> Rep DescribeDomains x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeDomains x -> DescribeDomains
$cfrom :: forall x. DescribeDomains -> Rep DescribeDomains x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDomains' 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:
--
-- 'domainNames', 'describeDomains_domainNames' - The names of the domains you want to include in the response.
newDescribeDomains ::
  DescribeDomains
newDescribeDomains :: DescribeDomains
newDescribeDomains =
  DescribeDomains' {$sel:domainNames:DescribeDomains' :: Maybe [Text]
domainNames = forall a. Maybe a
Prelude.Nothing}

-- | The names of the domains you want to include in the response.
describeDomains_domainNames :: Lens.Lens' DescribeDomains (Prelude.Maybe [Prelude.Text])
describeDomains_domainNames :: Lens' DescribeDomains (Maybe [Text])
describeDomains_domainNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDomains' {Maybe [Text]
domainNames :: Maybe [Text]
$sel:domainNames:DescribeDomains' :: DescribeDomains -> Maybe [Text]
domainNames} -> Maybe [Text]
domainNames) (\s :: DescribeDomains
s@DescribeDomains' {} Maybe [Text]
a -> DescribeDomains
s {$sel:domainNames:DescribeDomains' :: Maybe [Text]
domainNames = Maybe [Text]
a} :: DescribeDomains) 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

instance Core.AWSRequest DescribeDomains where
  type
    AWSResponse DescribeDomains =
      DescribeDomainsResponse
  request :: (Service -> Service) -> DescribeDomains -> Request DescribeDomains
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeDomains
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeDomains)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeDomainsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> [DomainStatus] -> DescribeDomainsResponse
DescribeDomainsResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DomainStatusList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member"
                        )
      )

instance Prelude.Hashable DescribeDomains where
  hashWithSalt :: Int -> DescribeDomains -> Int
hashWithSalt Int
_salt DescribeDomains' {Maybe [Text]
domainNames :: Maybe [Text]
$sel:domainNames:DescribeDomains' :: DescribeDomains -> Maybe [Text]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
domainNames

instance Prelude.NFData DescribeDomains where
  rnf :: DescribeDomains -> ()
rnf DescribeDomains' {Maybe [Text]
domainNames :: Maybe [Text]
$sel:domainNames:DescribeDomains' :: DescribeDomains -> Maybe [Text]
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
domainNames

instance Data.ToHeaders DescribeDomains where
  toHeaders :: DescribeDomains -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DescribeDomains where
  toQuery :: DescribeDomains -> QueryString
toQuery DescribeDomains' {Maybe [Text]
domainNames :: Maybe [Text]
$sel:domainNames:DescribeDomains' :: DescribeDomains -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeDomains" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2013-01-01" :: Prelude.ByteString),
        ByteString
"DomainNames"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
domainNames)
      ]

-- | The result of a @DescribeDomains@ request. Contains the status of the
-- domains specified in the request or all domains owned by the account.
--
-- /See:/ 'newDescribeDomainsResponse' smart constructor.
data DescribeDomainsResponse = DescribeDomainsResponse'
  { -- | The response's http status code.
    DescribeDomainsResponse -> Int
httpStatus :: Prelude.Int,
    DescribeDomainsResponse -> [DomainStatus]
domainStatusList :: [DomainStatus]
  }
  deriving (DescribeDomainsResponse -> DescribeDomainsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDomainsResponse -> DescribeDomainsResponse -> Bool
$c/= :: DescribeDomainsResponse -> DescribeDomainsResponse -> Bool
== :: DescribeDomainsResponse -> DescribeDomainsResponse -> Bool
$c== :: DescribeDomainsResponse -> DescribeDomainsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeDomainsResponse]
ReadPrec DescribeDomainsResponse
Int -> ReadS DescribeDomainsResponse
ReadS [DescribeDomainsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDomainsResponse]
$creadListPrec :: ReadPrec [DescribeDomainsResponse]
readPrec :: ReadPrec DescribeDomainsResponse
$creadPrec :: ReadPrec DescribeDomainsResponse
readList :: ReadS [DescribeDomainsResponse]
$creadList :: ReadS [DescribeDomainsResponse]
readsPrec :: Int -> ReadS DescribeDomainsResponse
$creadsPrec :: Int -> ReadS DescribeDomainsResponse
Prelude.Read, Int -> DescribeDomainsResponse -> ShowS
[DescribeDomainsResponse] -> ShowS
DescribeDomainsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDomainsResponse] -> ShowS
$cshowList :: [DescribeDomainsResponse] -> ShowS
show :: DescribeDomainsResponse -> String
$cshow :: DescribeDomainsResponse -> String
showsPrec :: Int -> DescribeDomainsResponse -> ShowS
$cshowsPrec :: Int -> DescribeDomainsResponse -> ShowS
Prelude.Show, forall x. Rep DescribeDomainsResponse x -> DescribeDomainsResponse
forall x. DescribeDomainsResponse -> Rep DescribeDomainsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeDomainsResponse x -> DescribeDomainsResponse
$cfrom :: forall x. DescribeDomainsResponse -> Rep DescribeDomainsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDomainsResponse' 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', 'describeDomainsResponse_httpStatus' - The response's http status code.
--
-- 'domainStatusList', 'describeDomainsResponse_domainStatusList' - Undocumented member.
newDescribeDomainsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDomainsResponse
newDescribeDomainsResponse :: Int -> DescribeDomainsResponse
newDescribeDomainsResponse Int
pHttpStatus_ =
  DescribeDomainsResponse'
    { $sel:httpStatus:DescribeDomainsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:domainStatusList:DescribeDomainsResponse' :: [DomainStatus]
domainStatusList = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | Undocumented member.
describeDomainsResponse_domainStatusList :: Lens.Lens' DescribeDomainsResponse [DomainStatus]
describeDomainsResponse_domainStatusList :: Lens' DescribeDomainsResponse [DomainStatus]
describeDomainsResponse_domainStatusList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDomainsResponse' {[DomainStatus]
domainStatusList :: [DomainStatus]
$sel:domainStatusList:DescribeDomainsResponse' :: DescribeDomainsResponse -> [DomainStatus]
domainStatusList} -> [DomainStatus]
domainStatusList) (\s :: DescribeDomainsResponse
s@DescribeDomainsResponse' {} [DomainStatus]
a -> DescribeDomainsResponse
s {$sel:domainStatusList:DescribeDomainsResponse' :: [DomainStatus]
domainStatusList = [DomainStatus]
a} :: DescribeDomainsResponse) 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 Prelude.NFData DescribeDomainsResponse where
  rnf :: DescribeDomainsResponse -> ()
rnf DescribeDomainsResponse' {Int
[DomainStatus]
domainStatusList :: [DomainStatus]
httpStatus :: Int
$sel:domainStatusList:DescribeDomainsResponse' :: DescribeDomainsResponse -> [DomainStatus]
$sel:httpStatus:DescribeDomainsResponse' :: DescribeDomainsResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [DomainStatus]
domainStatusList