{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Kendra.Types.SortingConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Kendra.Types.SortingConfiguration where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kendra.Types.SortOrder
import qualified Amazonka.Prelude as Prelude

-- | Specifies the document attribute to use to sort the response to a Amazon
-- Kendra query. You can specify a single attribute for sorting. The
-- attribute must have the @Sortable@ flag set to @true@, otherwise Amazon
-- Kendra returns an exception.
--
-- You can sort attributes of the following types.
--
-- -   Date value
--
-- -   Long value
--
-- -   String value
--
-- You can\'t sort attributes of the following type.
--
-- -   String list value
--
-- /See:/ 'newSortingConfiguration' smart constructor.
data SortingConfiguration = SortingConfiguration'
  { -- | The name of the document attribute used to sort the response. You can
    -- use any field that has the @Sortable@ flag set to true.
    --
    -- You can also sort by any of the following built-in attributes:
    --
    -- -   _category
    --
    -- -   _created_at
    --
    -- -   _last_updated_at
    --
    -- -   _version
    --
    -- -   _view_count
    SortingConfiguration -> Text
documentAttributeKey :: Prelude.Text,
    -- | The order that the results should be returned in. In case of ties, the
    -- relevance assigned to the result by Amazon Kendra is used as the
    -- tie-breaker.
    SortingConfiguration -> SortOrder
sortOrder :: SortOrder
  }
  deriving (SortingConfiguration -> SortingConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortingConfiguration -> SortingConfiguration -> Bool
$c/= :: SortingConfiguration -> SortingConfiguration -> Bool
== :: SortingConfiguration -> SortingConfiguration -> Bool
$c== :: SortingConfiguration -> SortingConfiguration -> Bool
Prelude.Eq, ReadPrec [SortingConfiguration]
ReadPrec SortingConfiguration
Int -> ReadS SortingConfiguration
ReadS [SortingConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SortingConfiguration]
$creadListPrec :: ReadPrec [SortingConfiguration]
readPrec :: ReadPrec SortingConfiguration
$creadPrec :: ReadPrec SortingConfiguration
readList :: ReadS [SortingConfiguration]
$creadList :: ReadS [SortingConfiguration]
readsPrec :: Int -> ReadS SortingConfiguration
$creadsPrec :: Int -> ReadS SortingConfiguration
Prelude.Read, Int -> SortingConfiguration -> ShowS
[SortingConfiguration] -> ShowS
SortingConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortingConfiguration] -> ShowS
$cshowList :: [SortingConfiguration] -> ShowS
show :: SortingConfiguration -> String
$cshow :: SortingConfiguration -> String
showsPrec :: Int -> SortingConfiguration -> ShowS
$cshowsPrec :: Int -> SortingConfiguration -> ShowS
Prelude.Show, forall x. Rep SortingConfiguration x -> SortingConfiguration
forall x. SortingConfiguration -> Rep SortingConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SortingConfiguration x -> SortingConfiguration
$cfrom :: forall x. SortingConfiguration -> Rep SortingConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'SortingConfiguration' 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:
--
-- 'documentAttributeKey', 'sortingConfiguration_documentAttributeKey' - The name of the document attribute used to sort the response. You can
-- use any field that has the @Sortable@ flag set to true.
--
-- You can also sort by any of the following built-in attributes:
--
-- -   _category
--
-- -   _created_at
--
-- -   _last_updated_at
--
-- -   _version
--
-- -   _view_count
--
-- 'sortOrder', 'sortingConfiguration_sortOrder' - The order that the results should be returned in. In case of ties, the
-- relevance assigned to the result by Amazon Kendra is used as the
-- tie-breaker.
newSortingConfiguration ::
  -- | 'documentAttributeKey'
  Prelude.Text ->
  -- | 'sortOrder'
  SortOrder ->
  SortingConfiguration
newSortingConfiguration :: Text -> SortOrder -> SortingConfiguration
newSortingConfiguration
  Text
pDocumentAttributeKey_
  SortOrder
pSortOrder_ =
    SortingConfiguration'
      { $sel:documentAttributeKey:SortingConfiguration' :: Text
documentAttributeKey =
          Text
pDocumentAttributeKey_,
        $sel:sortOrder:SortingConfiguration' :: SortOrder
sortOrder = SortOrder
pSortOrder_
      }

-- | The name of the document attribute used to sort the response. You can
-- use any field that has the @Sortable@ flag set to true.
--
-- You can also sort by any of the following built-in attributes:
--
-- -   _category
--
-- -   _created_at
--
-- -   _last_updated_at
--
-- -   _version
--
-- -   _view_count
sortingConfiguration_documentAttributeKey :: Lens.Lens' SortingConfiguration Prelude.Text
sortingConfiguration_documentAttributeKey :: Lens' SortingConfiguration Text
sortingConfiguration_documentAttributeKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SortingConfiguration' {Text
documentAttributeKey :: Text
$sel:documentAttributeKey:SortingConfiguration' :: SortingConfiguration -> Text
documentAttributeKey} -> Text
documentAttributeKey) (\s :: SortingConfiguration
s@SortingConfiguration' {} Text
a -> SortingConfiguration
s {$sel:documentAttributeKey:SortingConfiguration' :: Text
documentAttributeKey = Text
a} :: SortingConfiguration)

-- | The order that the results should be returned in. In case of ties, the
-- relevance assigned to the result by Amazon Kendra is used as the
-- tie-breaker.
sortingConfiguration_sortOrder :: Lens.Lens' SortingConfiguration SortOrder
sortingConfiguration_sortOrder :: Lens' SortingConfiguration SortOrder
sortingConfiguration_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SortingConfiguration' {SortOrder
sortOrder :: SortOrder
$sel:sortOrder:SortingConfiguration' :: SortingConfiguration -> SortOrder
sortOrder} -> SortOrder
sortOrder) (\s :: SortingConfiguration
s@SortingConfiguration' {} SortOrder
a -> SortingConfiguration
s {$sel:sortOrder:SortingConfiguration' :: SortOrder
sortOrder = SortOrder
a} :: SortingConfiguration)

instance Prelude.Hashable SortingConfiguration where
  hashWithSalt :: Int -> SortingConfiguration -> Int
hashWithSalt Int
_salt SortingConfiguration' {Text
SortOrder
sortOrder :: SortOrder
documentAttributeKey :: Text
$sel:sortOrder:SortingConfiguration' :: SortingConfiguration -> SortOrder
$sel:documentAttributeKey:SortingConfiguration' :: SortingConfiguration -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
documentAttributeKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SortOrder
sortOrder

instance Prelude.NFData SortingConfiguration where
  rnf :: SortingConfiguration -> ()
rnf SortingConfiguration' {Text
SortOrder
sortOrder :: SortOrder
documentAttributeKey :: Text
$sel:sortOrder:SortingConfiguration' :: SortingConfiguration -> SortOrder
$sel:documentAttributeKey:SortingConfiguration' :: SortingConfiguration -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
documentAttributeKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SortOrder
sortOrder

instance Data.ToJSON SortingConfiguration where
  toJSON :: SortingConfiguration -> Value
toJSON SortingConfiguration' {Text
SortOrder
sortOrder :: SortOrder
documentAttributeKey :: Text
$sel:sortOrder:SortingConfiguration' :: SortingConfiguration -> SortOrder
$sel:documentAttributeKey:SortingConfiguration' :: SortingConfiguration -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"DocumentAttributeKey"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
documentAttributeKey
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"SortOrder" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= SortOrder
sortOrder)
          ]
      )