{-# 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.Relevance
-- 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.Relevance 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.Order
import qualified Amazonka.Prelude as Prelude

-- | Provides information for tuning the relevance of a field in a search.
-- When a query includes terms that match the field, the results are given
-- a boost in the response based on these tuning parameters.
--
-- /See:/ 'newRelevance' smart constructor.
data Relevance = Relevance'
  { -- | Specifies the time period that the boost applies to. For example, to
    -- make the boost apply to documents with the field value within the last
    -- month, you would use \"2628000s\". Once the field value is beyond the
    -- specified range, the effect of the boost drops off. The higher the
    -- importance, the faster the effect drops off. If you don\'t specify a
    -- value, the default is 3 months. The value of the field is a numeric
    -- string followed by the character \"s\", for example \"86400s\" for one
    -- day, or \"604800s\" for one week.
    --
    -- Only applies to @DATE@ fields.
    Relevance -> Maybe Text
duration :: Prelude.Maybe Prelude.Text,
    -- | Indicates that this field determines how \"fresh\" a document is. For
    -- example, if document 1 was created on November 5, and document 2 was
    -- created on October 31, document 1 is \"fresher\" than document 2. You
    -- can only set the @Freshness@ field on one @DATE@ type field. Only
    -- applies to @DATE@ fields.
    Relevance -> Maybe Bool
freshness :: Prelude.Maybe Prelude.Bool,
    -- | The relative importance of the field in the search. Larger numbers
    -- provide more of a boost than smaller numbers.
    Relevance -> Maybe Natural
importance :: Prelude.Maybe Prelude.Natural,
    -- | Determines how values should be interpreted.
    --
    -- When the @RankOrder@ field is @ASCENDING@, higher numbers are better.
    -- For example, a document with a rating score of 10 is higher ranking than
    -- a document with a rating score of 1.
    --
    -- When the @RankOrder@ field is @DESCENDING@, lower numbers are better.
    -- For example, in a task tracking application, a priority 1 task is more
    -- important than a priority 5 task.
    --
    -- Only applies to @LONG@ and @DOUBLE@ fields.
    Relevance -> Maybe Order
rankOrder :: Prelude.Maybe Order,
    -- | A list of values that should be given a different boost when they appear
    -- in the result list. For example, if you are boosting a field called
    -- \"department,\" query terms that match the department field are boosted
    -- in the result. However, you can add entries from the department field to
    -- boost documents with those values higher.
    --
    -- For example, you can add entries to the map with names of departments.
    -- If you add \"HR\",5 and \"Legal\",3 those departments are given special
    -- attention when they appear in the metadata of a document. When those
    -- terms appear they are given the specified importance instead of the
    -- regular importance for the boost.
    Relevance -> Maybe (HashMap Text Natural)
valueImportanceMap :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Natural)
  }
  deriving (Relevance -> Relevance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Relevance -> Relevance -> Bool
$c/= :: Relevance -> Relevance -> Bool
== :: Relevance -> Relevance -> Bool
$c== :: Relevance -> Relevance -> Bool
Prelude.Eq, ReadPrec [Relevance]
ReadPrec Relevance
Int -> ReadS Relevance
ReadS [Relevance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Relevance]
$creadListPrec :: ReadPrec [Relevance]
readPrec :: ReadPrec Relevance
$creadPrec :: ReadPrec Relevance
readList :: ReadS [Relevance]
$creadList :: ReadS [Relevance]
readsPrec :: Int -> ReadS Relevance
$creadsPrec :: Int -> ReadS Relevance
Prelude.Read, Int -> Relevance -> ShowS
[Relevance] -> ShowS
Relevance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Relevance] -> ShowS
$cshowList :: [Relevance] -> ShowS
show :: Relevance -> String
$cshow :: Relevance -> String
showsPrec :: Int -> Relevance -> ShowS
$cshowsPrec :: Int -> Relevance -> ShowS
Prelude.Show, forall x. Rep Relevance x -> Relevance
forall x. Relevance -> Rep Relevance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Relevance x -> Relevance
$cfrom :: forall x. Relevance -> Rep Relevance x
Prelude.Generic)

-- |
-- Create a value of 'Relevance' 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:
--
-- 'duration', 'relevance_duration' - Specifies the time period that the boost applies to. For example, to
-- make the boost apply to documents with the field value within the last
-- month, you would use \"2628000s\". Once the field value is beyond the
-- specified range, the effect of the boost drops off. The higher the
-- importance, the faster the effect drops off. If you don\'t specify a
-- value, the default is 3 months. The value of the field is a numeric
-- string followed by the character \"s\", for example \"86400s\" for one
-- day, or \"604800s\" for one week.
--
-- Only applies to @DATE@ fields.
--
-- 'freshness', 'relevance_freshness' - Indicates that this field determines how \"fresh\" a document is. For
-- example, if document 1 was created on November 5, and document 2 was
-- created on October 31, document 1 is \"fresher\" than document 2. You
-- can only set the @Freshness@ field on one @DATE@ type field. Only
-- applies to @DATE@ fields.
--
-- 'importance', 'relevance_importance' - The relative importance of the field in the search. Larger numbers
-- provide more of a boost than smaller numbers.
--
-- 'rankOrder', 'relevance_rankOrder' - Determines how values should be interpreted.
--
-- When the @RankOrder@ field is @ASCENDING@, higher numbers are better.
-- For example, a document with a rating score of 10 is higher ranking than
-- a document with a rating score of 1.
--
-- When the @RankOrder@ field is @DESCENDING@, lower numbers are better.
-- For example, in a task tracking application, a priority 1 task is more
-- important than a priority 5 task.
--
-- Only applies to @LONG@ and @DOUBLE@ fields.
--
-- 'valueImportanceMap', 'relevance_valueImportanceMap' - A list of values that should be given a different boost when they appear
-- in the result list. For example, if you are boosting a field called
-- \"department,\" query terms that match the department field are boosted
-- in the result. However, you can add entries from the department field to
-- boost documents with those values higher.
--
-- For example, you can add entries to the map with names of departments.
-- If you add \"HR\",5 and \"Legal\",3 those departments are given special
-- attention when they appear in the metadata of a document. When those
-- terms appear they are given the specified importance instead of the
-- regular importance for the boost.
newRelevance ::
  Relevance
newRelevance :: Relevance
newRelevance =
  Relevance'
    { $sel:duration:Relevance' :: Maybe Text
duration = forall a. Maybe a
Prelude.Nothing,
      $sel:freshness:Relevance' :: Maybe Bool
freshness = forall a. Maybe a
Prelude.Nothing,
      $sel:importance:Relevance' :: Maybe Natural
importance = forall a. Maybe a
Prelude.Nothing,
      $sel:rankOrder:Relevance' :: Maybe Order
rankOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:valueImportanceMap:Relevance' :: Maybe (HashMap Text Natural)
valueImportanceMap = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies the time period that the boost applies to. For example, to
-- make the boost apply to documents with the field value within the last
-- month, you would use \"2628000s\". Once the field value is beyond the
-- specified range, the effect of the boost drops off. The higher the
-- importance, the faster the effect drops off. If you don\'t specify a
-- value, the default is 3 months. The value of the field is a numeric
-- string followed by the character \"s\", for example \"86400s\" for one
-- day, or \"604800s\" for one week.
--
-- Only applies to @DATE@ fields.
relevance_duration :: Lens.Lens' Relevance (Prelude.Maybe Prelude.Text)
relevance_duration :: Lens' Relevance (Maybe Text)
relevance_duration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Relevance' {Maybe Text
duration :: Maybe Text
$sel:duration:Relevance' :: Relevance -> Maybe Text
duration} -> Maybe Text
duration) (\s :: Relevance
s@Relevance' {} Maybe Text
a -> Relevance
s {$sel:duration:Relevance' :: Maybe Text
duration = Maybe Text
a} :: Relevance)

-- | Indicates that this field determines how \"fresh\" a document is. For
-- example, if document 1 was created on November 5, and document 2 was
-- created on October 31, document 1 is \"fresher\" than document 2. You
-- can only set the @Freshness@ field on one @DATE@ type field. Only
-- applies to @DATE@ fields.
relevance_freshness :: Lens.Lens' Relevance (Prelude.Maybe Prelude.Bool)
relevance_freshness :: Lens' Relevance (Maybe Bool)
relevance_freshness = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Relevance' {Maybe Bool
freshness :: Maybe Bool
$sel:freshness:Relevance' :: Relevance -> Maybe Bool
freshness} -> Maybe Bool
freshness) (\s :: Relevance
s@Relevance' {} Maybe Bool
a -> Relevance
s {$sel:freshness:Relevance' :: Maybe Bool
freshness = Maybe Bool
a} :: Relevance)

-- | The relative importance of the field in the search. Larger numbers
-- provide more of a boost than smaller numbers.
relevance_importance :: Lens.Lens' Relevance (Prelude.Maybe Prelude.Natural)
relevance_importance :: Lens' Relevance (Maybe Natural)
relevance_importance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Relevance' {Maybe Natural
importance :: Maybe Natural
$sel:importance:Relevance' :: Relevance -> Maybe Natural
importance} -> Maybe Natural
importance) (\s :: Relevance
s@Relevance' {} Maybe Natural
a -> Relevance
s {$sel:importance:Relevance' :: Maybe Natural
importance = Maybe Natural
a} :: Relevance)

-- | Determines how values should be interpreted.
--
-- When the @RankOrder@ field is @ASCENDING@, higher numbers are better.
-- For example, a document with a rating score of 10 is higher ranking than
-- a document with a rating score of 1.
--
-- When the @RankOrder@ field is @DESCENDING@, lower numbers are better.
-- For example, in a task tracking application, a priority 1 task is more
-- important than a priority 5 task.
--
-- Only applies to @LONG@ and @DOUBLE@ fields.
relevance_rankOrder :: Lens.Lens' Relevance (Prelude.Maybe Order)
relevance_rankOrder :: Lens' Relevance (Maybe Order)
relevance_rankOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Relevance' {Maybe Order
rankOrder :: Maybe Order
$sel:rankOrder:Relevance' :: Relevance -> Maybe Order
rankOrder} -> Maybe Order
rankOrder) (\s :: Relevance
s@Relevance' {} Maybe Order
a -> Relevance
s {$sel:rankOrder:Relevance' :: Maybe Order
rankOrder = Maybe Order
a} :: Relevance)

-- | A list of values that should be given a different boost when they appear
-- in the result list. For example, if you are boosting a field called
-- \"department,\" query terms that match the department field are boosted
-- in the result. However, you can add entries from the department field to
-- boost documents with those values higher.
--
-- For example, you can add entries to the map with names of departments.
-- If you add \"HR\",5 and \"Legal\",3 those departments are given special
-- attention when they appear in the metadata of a document. When those
-- terms appear they are given the specified importance instead of the
-- regular importance for the boost.
relevance_valueImportanceMap :: Lens.Lens' Relevance (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Natural))
relevance_valueImportanceMap :: Lens' Relevance (Maybe (HashMap Text Natural))
relevance_valueImportanceMap = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Relevance' {Maybe (HashMap Text Natural)
valueImportanceMap :: Maybe (HashMap Text Natural)
$sel:valueImportanceMap:Relevance' :: Relevance -> Maybe (HashMap Text Natural)
valueImportanceMap} -> Maybe (HashMap Text Natural)
valueImportanceMap) (\s :: Relevance
s@Relevance' {} Maybe (HashMap Text Natural)
a -> Relevance
s {$sel:valueImportanceMap:Relevance' :: Maybe (HashMap Text Natural)
valueImportanceMap = Maybe (HashMap Text Natural)
a} :: Relevance) 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 Data.FromJSON Relevance where
  parseJSON :: Value -> Parser Relevance
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Relevance"
      ( \Object
x ->
          Maybe Text
-> Maybe Bool
-> Maybe Natural
-> Maybe Order
-> Maybe (HashMap Text Natural)
-> Relevance
Relevance'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Duration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Freshness")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Importance")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RankOrder")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ValueImportanceMap"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable Relevance where
  hashWithSalt :: Int -> Relevance -> Int
hashWithSalt Int
_salt Relevance' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text Natural)
Maybe Order
valueImportanceMap :: Maybe (HashMap Text Natural)
rankOrder :: Maybe Order
importance :: Maybe Natural
freshness :: Maybe Bool
duration :: Maybe Text
$sel:valueImportanceMap:Relevance' :: Relevance -> Maybe (HashMap Text Natural)
$sel:rankOrder:Relevance' :: Relevance -> Maybe Order
$sel:importance:Relevance' :: Relevance -> Maybe Natural
$sel:freshness:Relevance' :: Relevance -> Maybe Bool
$sel:duration:Relevance' :: Relevance -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
duration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
freshness
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
importance
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Order
rankOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Natural)
valueImportanceMap

instance Prelude.NFData Relevance where
  rnf :: Relevance -> ()
rnf Relevance' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text Natural)
Maybe Order
valueImportanceMap :: Maybe (HashMap Text Natural)
rankOrder :: Maybe Order
importance :: Maybe Natural
freshness :: Maybe Bool
duration :: Maybe Text
$sel:valueImportanceMap:Relevance' :: Relevance -> Maybe (HashMap Text Natural)
$sel:rankOrder:Relevance' :: Relevance -> Maybe Order
$sel:importance:Relevance' :: Relevance -> Maybe Natural
$sel:freshness:Relevance' :: Relevance -> Maybe Bool
$sel:duration:Relevance' :: Relevance -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
duration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
freshness
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
importance
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Order
rankOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Natural)
valueImportanceMap

instance Data.ToJSON Relevance where
  toJSON :: Relevance -> Value
toJSON Relevance' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text Natural)
Maybe Order
valueImportanceMap :: Maybe (HashMap Text Natural)
rankOrder :: Maybe Order
importance :: Maybe Natural
freshness :: Maybe Bool
duration :: Maybe Text
$sel:valueImportanceMap:Relevance' :: Relevance -> Maybe (HashMap Text Natural)
$sel:rankOrder:Relevance' :: Relevance -> Maybe Order
$sel:importance:Relevance' :: Relevance -> Maybe Natural
$sel:freshness:Relevance' :: Relevance -> Maybe Bool
$sel:duration:Relevance' :: Relevance -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Duration" 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
duration,
            (Key
"Freshness" 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 Bool
freshness,
            (Key
"Importance" 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 Natural
importance,
            (Key
"RankOrder" 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 Order
rankOrder,
            (Key
"ValueImportanceMap" 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 (HashMap Text Natural)
valueImportanceMap
          ]
      )