{-# 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.DescribeIndexFields
-- 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 index fields configured for the search
-- domain. Can be limited to specific fields by name. By default, shows all
-- fields and includes any pending changes to the configuration. Set the
-- @Deployed@ option to @true@ to show the active configuration and exclude
-- pending changes. For more information, see
-- <http://docs.aws.amazon.com/cloudsearch/latest/developerguide/getting-domain-info.html Getting Domain Information>
-- in the /Amazon CloudSearch Developer Guide/.
module Amazonka.CloudSearch.DescribeIndexFields
  ( -- * Creating a Request
    DescribeIndexFields (..),
    newDescribeIndexFields,

    -- * Request Lenses
    describeIndexFields_deployed,
    describeIndexFields_fieldNames,
    describeIndexFields_domainName,

    -- * Destructuring the Response
    DescribeIndexFieldsResponse (..),
    newDescribeIndexFieldsResponse,

    -- * Response Lenses
    describeIndexFieldsResponse_httpStatus,
    describeIndexFieldsResponse_indexFields,
  )
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 @DescribeIndexFields@ operation.
-- Specifies the name of the domain you want to describe. To restrict the
-- response to particular index fields, specify the names of the index
-- fields you want to describe. To show the active configuration and
-- exclude any pending changes, set the @Deployed@ option to @true@.
--
-- /See:/ 'newDescribeIndexFields' smart constructor.
data DescribeIndexFields = DescribeIndexFields'
  { -- | Whether to display the deployed configuration (@true@) or include any
    -- pending changes (@false@). Defaults to @false@.
    DescribeIndexFields -> Maybe Bool
deployed :: Prelude.Maybe Prelude.Bool,
    -- | A list of the index fields you want to describe. If not specified,
    -- information is returned for all configured index fields.
    DescribeIndexFields -> Maybe [Text]
fieldNames :: Prelude.Maybe [Prelude.Text],
    -- | The name of the domain you want to describe.
    DescribeIndexFields -> Text
domainName :: Prelude.Text
  }
  deriving (DescribeIndexFields -> DescribeIndexFields -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeIndexFields -> DescribeIndexFields -> Bool
$c/= :: DescribeIndexFields -> DescribeIndexFields -> Bool
== :: DescribeIndexFields -> DescribeIndexFields -> Bool
$c== :: DescribeIndexFields -> DescribeIndexFields -> Bool
Prelude.Eq, ReadPrec [DescribeIndexFields]
ReadPrec DescribeIndexFields
Int -> ReadS DescribeIndexFields
ReadS [DescribeIndexFields]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeIndexFields]
$creadListPrec :: ReadPrec [DescribeIndexFields]
readPrec :: ReadPrec DescribeIndexFields
$creadPrec :: ReadPrec DescribeIndexFields
readList :: ReadS [DescribeIndexFields]
$creadList :: ReadS [DescribeIndexFields]
readsPrec :: Int -> ReadS DescribeIndexFields
$creadsPrec :: Int -> ReadS DescribeIndexFields
Prelude.Read, Int -> DescribeIndexFields -> ShowS
[DescribeIndexFields] -> ShowS
DescribeIndexFields -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeIndexFields] -> ShowS
$cshowList :: [DescribeIndexFields] -> ShowS
show :: DescribeIndexFields -> String
$cshow :: DescribeIndexFields -> String
showsPrec :: Int -> DescribeIndexFields -> ShowS
$cshowsPrec :: Int -> DescribeIndexFields -> ShowS
Prelude.Show, forall x. Rep DescribeIndexFields x -> DescribeIndexFields
forall x. DescribeIndexFields -> Rep DescribeIndexFields x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeIndexFields x -> DescribeIndexFields
$cfrom :: forall x. DescribeIndexFields -> Rep DescribeIndexFields x
Prelude.Generic)

-- |
-- Create a value of 'DescribeIndexFields' 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:
--
-- 'deployed', 'describeIndexFields_deployed' - Whether to display the deployed configuration (@true@) or include any
-- pending changes (@false@). Defaults to @false@.
--
-- 'fieldNames', 'describeIndexFields_fieldNames' - A list of the index fields you want to describe. If not specified,
-- information is returned for all configured index fields.
--
-- 'domainName', 'describeIndexFields_domainName' - The name of the domain you want to describe.
newDescribeIndexFields ::
  -- | 'domainName'
  Prelude.Text ->
  DescribeIndexFields
newDescribeIndexFields :: Text -> DescribeIndexFields
newDescribeIndexFields Text
pDomainName_ =
  DescribeIndexFields'
    { $sel:deployed:DescribeIndexFields' :: Maybe Bool
deployed = forall a. Maybe a
Prelude.Nothing,
      $sel:fieldNames:DescribeIndexFields' :: Maybe [Text]
fieldNames = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:DescribeIndexFields' :: Text
domainName = Text
pDomainName_
    }

-- | Whether to display the deployed configuration (@true@) or include any
-- pending changes (@false@). Defaults to @false@.
describeIndexFields_deployed :: Lens.Lens' DescribeIndexFields (Prelude.Maybe Prelude.Bool)
describeIndexFields_deployed :: Lens' DescribeIndexFields (Maybe Bool)
describeIndexFields_deployed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeIndexFields' {Maybe Bool
deployed :: Maybe Bool
$sel:deployed:DescribeIndexFields' :: DescribeIndexFields -> Maybe Bool
deployed} -> Maybe Bool
deployed) (\s :: DescribeIndexFields
s@DescribeIndexFields' {} Maybe Bool
a -> DescribeIndexFields
s {$sel:deployed:DescribeIndexFields' :: Maybe Bool
deployed = Maybe Bool
a} :: DescribeIndexFields)

-- | A list of the index fields you want to describe. If not specified,
-- information is returned for all configured index fields.
describeIndexFields_fieldNames :: Lens.Lens' DescribeIndexFields (Prelude.Maybe [Prelude.Text])
describeIndexFields_fieldNames :: Lens' DescribeIndexFields (Maybe [Text])
describeIndexFields_fieldNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeIndexFields' {Maybe [Text]
fieldNames :: Maybe [Text]
$sel:fieldNames:DescribeIndexFields' :: DescribeIndexFields -> Maybe [Text]
fieldNames} -> Maybe [Text]
fieldNames) (\s :: DescribeIndexFields
s@DescribeIndexFields' {} Maybe [Text]
a -> DescribeIndexFields
s {$sel:fieldNames:DescribeIndexFields' :: Maybe [Text]
fieldNames = Maybe [Text]
a} :: DescribeIndexFields) 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 name of the domain you want to describe.
describeIndexFields_domainName :: Lens.Lens' DescribeIndexFields Prelude.Text
describeIndexFields_domainName :: Lens' DescribeIndexFields Text
describeIndexFields_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeIndexFields' {Text
domainName :: Text
$sel:domainName:DescribeIndexFields' :: DescribeIndexFields -> Text
domainName} -> Text
domainName) (\s :: DescribeIndexFields
s@DescribeIndexFields' {} Text
a -> DescribeIndexFields
s {$sel:domainName:DescribeIndexFields' :: Text
domainName = Text
a} :: DescribeIndexFields)

instance Core.AWSRequest DescribeIndexFields where
  type
    AWSResponse DescribeIndexFields =
      DescribeIndexFieldsResponse
  request :: (Service -> Service)
-> DescribeIndexFields -> Request DescribeIndexFields
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 DescribeIndexFields
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeIndexFields)))
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
"DescribeIndexFieldsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> [IndexFieldStatus] -> DescribeIndexFieldsResponse
DescribeIndexFieldsResponse'
            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
"IndexFields"
                            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 DescribeIndexFields where
  hashWithSalt :: Int -> DescribeIndexFields -> Int
hashWithSalt Int
_salt DescribeIndexFields' {Maybe Bool
Maybe [Text]
Text
domainName :: Text
fieldNames :: Maybe [Text]
deployed :: Maybe Bool
$sel:domainName:DescribeIndexFields' :: DescribeIndexFields -> Text
$sel:fieldNames:DescribeIndexFields' :: DescribeIndexFields -> Maybe [Text]
$sel:deployed:DescribeIndexFields' :: DescribeIndexFields -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deployed
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
fieldNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName

instance Prelude.NFData DescribeIndexFields where
  rnf :: DescribeIndexFields -> ()
rnf DescribeIndexFields' {Maybe Bool
Maybe [Text]
Text
domainName :: Text
fieldNames :: Maybe [Text]
deployed :: Maybe Bool
$sel:domainName:DescribeIndexFields' :: DescribeIndexFields -> Text
$sel:fieldNames:DescribeIndexFields' :: DescribeIndexFields -> Maybe [Text]
$sel:deployed:DescribeIndexFields' :: DescribeIndexFields -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deployed
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
fieldNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName

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

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

instance Data.ToQuery DescribeIndexFields where
  toQuery :: DescribeIndexFields -> QueryString
toQuery DescribeIndexFields' {Maybe Bool
Maybe [Text]
Text
domainName :: Text
fieldNames :: Maybe [Text]
deployed :: Maybe Bool
$sel:domainName:DescribeIndexFields' :: DescribeIndexFields -> Text
$sel:fieldNames:DescribeIndexFields' :: DescribeIndexFields -> Maybe [Text]
$sel:deployed:DescribeIndexFields' :: DescribeIndexFields -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeIndexFields" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2013-01-01" :: Prelude.ByteString),
        ByteString
"Deployed" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deployed,
        ByteString
"FieldNames"
          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]
fieldNames),
        ByteString
"DomainName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
domainName
      ]

-- | The result of a @DescribeIndexFields@ request. Contains the index fields
-- configured for the domain specified in the request.
--
-- /See:/ 'newDescribeIndexFieldsResponse' smart constructor.
data DescribeIndexFieldsResponse = DescribeIndexFieldsResponse'
  { -- | The response's http status code.
    DescribeIndexFieldsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The index fields configured for the domain.
    DescribeIndexFieldsResponse -> [IndexFieldStatus]
indexFields :: [IndexFieldStatus]
  }
  deriving (DescribeIndexFieldsResponse -> DescribeIndexFieldsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeIndexFieldsResponse -> DescribeIndexFieldsResponse -> Bool
$c/= :: DescribeIndexFieldsResponse -> DescribeIndexFieldsResponse -> Bool
== :: DescribeIndexFieldsResponse -> DescribeIndexFieldsResponse -> Bool
$c== :: DescribeIndexFieldsResponse -> DescribeIndexFieldsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeIndexFieldsResponse]
ReadPrec DescribeIndexFieldsResponse
Int -> ReadS DescribeIndexFieldsResponse
ReadS [DescribeIndexFieldsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeIndexFieldsResponse]
$creadListPrec :: ReadPrec [DescribeIndexFieldsResponse]
readPrec :: ReadPrec DescribeIndexFieldsResponse
$creadPrec :: ReadPrec DescribeIndexFieldsResponse
readList :: ReadS [DescribeIndexFieldsResponse]
$creadList :: ReadS [DescribeIndexFieldsResponse]
readsPrec :: Int -> ReadS DescribeIndexFieldsResponse
$creadsPrec :: Int -> ReadS DescribeIndexFieldsResponse
Prelude.Read, Int -> DescribeIndexFieldsResponse -> ShowS
[DescribeIndexFieldsResponse] -> ShowS
DescribeIndexFieldsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeIndexFieldsResponse] -> ShowS
$cshowList :: [DescribeIndexFieldsResponse] -> ShowS
show :: DescribeIndexFieldsResponse -> String
$cshow :: DescribeIndexFieldsResponse -> String
showsPrec :: Int -> DescribeIndexFieldsResponse -> ShowS
$cshowsPrec :: Int -> DescribeIndexFieldsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeIndexFieldsResponse x -> DescribeIndexFieldsResponse
forall x.
DescribeIndexFieldsResponse -> Rep DescribeIndexFieldsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeIndexFieldsResponse x -> DescribeIndexFieldsResponse
$cfrom :: forall x.
DescribeIndexFieldsResponse -> Rep DescribeIndexFieldsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeIndexFieldsResponse' 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', 'describeIndexFieldsResponse_httpStatus' - The response's http status code.
--
-- 'indexFields', 'describeIndexFieldsResponse_indexFields' - The index fields configured for the domain.
newDescribeIndexFieldsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeIndexFieldsResponse
newDescribeIndexFieldsResponse :: Int -> DescribeIndexFieldsResponse
newDescribeIndexFieldsResponse Int
pHttpStatus_ =
  DescribeIndexFieldsResponse'
    { $sel:httpStatus:DescribeIndexFieldsResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:indexFields:DescribeIndexFieldsResponse' :: [IndexFieldStatus]
indexFields = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | The index fields configured for the domain.
describeIndexFieldsResponse_indexFields :: Lens.Lens' DescribeIndexFieldsResponse [IndexFieldStatus]
describeIndexFieldsResponse_indexFields :: Lens' DescribeIndexFieldsResponse [IndexFieldStatus]
describeIndexFieldsResponse_indexFields = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeIndexFieldsResponse' {[IndexFieldStatus]
indexFields :: [IndexFieldStatus]
$sel:indexFields:DescribeIndexFieldsResponse' :: DescribeIndexFieldsResponse -> [IndexFieldStatus]
indexFields} -> [IndexFieldStatus]
indexFields) (\s :: DescribeIndexFieldsResponse
s@DescribeIndexFieldsResponse' {} [IndexFieldStatus]
a -> DescribeIndexFieldsResponse
s {$sel:indexFields:DescribeIndexFieldsResponse' :: [IndexFieldStatus]
indexFields = [IndexFieldStatus]
a} :: DescribeIndexFieldsResponse) 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 DescribeIndexFieldsResponse where
  rnf :: DescribeIndexFieldsResponse -> ()
rnf DescribeIndexFieldsResponse' {Int
[IndexFieldStatus]
indexFields :: [IndexFieldStatus]
httpStatus :: Int
$sel:indexFields:DescribeIndexFieldsResponse' :: DescribeIndexFieldsResponse -> [IndexFieldStatus]
$sel:httpStatus:DescribeIndexFieldsResponse' :: DescribeIndexFieldsResponse -> 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 [IndexFieldStatus]
indexFields