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

-- | An attribute returned with a document from a search.
--
-- /See:/ 'newAdditionalResultAttributeValue' smart constructor.
data AdditionalResultAttributeValue = AdditionalResultAttributeValue'
  { -- | The text associated with the attribute and information about the
    -- highlight to apply to the text.
    AdditionalResultAttributeValue -> Maybe TextWithHighlights
textWithHighlightsValue :: Prelude.Maybe TextWithHighlights
  }
  deriving (AdditionalResultAttributeValue
-> AdditionalResultAttributeValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdditionalResultAttributeValue
-> AdditionalResultAttributeValue -> Bool
$c/= :: AdditionalResultAttributeValue
-> AdditionalResultAttributeValue -> Bool
== :: AdditionalResultAttributeValue
-> AdditionalResultAttributeValue -> Bool
$c== :: AdditionalResultAttributeValue
-> AdditionalResultAttributeValue -> Bool
Prelude.Eq, ReadPrec [AdditionalResultAttributeValue]
ReadPrec AdditionalResultAttributeValue
Int -> ReadS AdditionalResultAttributeValue
ReadS [AdditionalResultAttributeValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdditionalResultAttributeValue]
$creadListPrec :: ReadPrec [AdditionalResultAttributeValue]
readPrec :: ReadPrec AdditionalResultAttributeValue
$creadPrec :: ReadPrec AdditionalResultAttributeValue
readList :: ReadS [AdditionalResultAttributeValue]
$creadList :: ReadS [AdditionalResultAttributeValue]
readsPrec :: Int -> ReadS AdditionalResultAttributeValue
$creadsPrec :: Int -> ReadS AdditionalResultAttributeValue
Prelude.Read, Int -> AdditionalResultAttributeValue -> ShowS
[AdditionalResultAttributeValue] -> ShowS
AdditionalResultAttributeValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdditionalResultAttributeValue] -> ShowS
$cshowList :: [AdditionalResultAttributeValue] -> ShowS
show :: AdditionalResultAttributeValue -> String
$cshow :: AdditionalResultAttributeValue -> String
showsPrec :: Int -> AdditionalResultAttributeValue -> ShowS
$cshowsPrec :: Int -> AdditionalResultAttributeValue -> ShowS
Prelude.Show, forall x.
Rep AdditionalResultAttributeValue x
-> AdditionalResultAttributeValue
forall x.
AdditionalResultAttributeValue
-> Rep AdditionalResultAttributeValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AdditionalResultAttributeValue x
-> AdditionalResultAttributeValue
$cfrom :: forall x.
AdditionalResultAttributeValue
-> Rep AdditionalResultAttributeValue x
Prelude.Generic)

-- |
-- Create a value of 'AdditionalResultAttributeValue' 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:
--
-- 'textWithHighlightsValue', 'additionalResultAttributeValue_textWithHighlightsValue' - The text associated with the attribute and information about the
-- highlight to apply to the text.
newAdditionalResultAttributeValue ::
  AdditionalResultAttributeValue
newAdditionalResultAttributeValue :: AdditionalResultAttributeValue
newAdditionalResultAttributeValue =
  AdditionalResultAttributeValue'
    { $sel:textWithHighlightsValue:AdditionalResultAttributeValue' :: Maybe TextWithHighlights
textWithHighlightsValue =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The text associated with the attribute and information about the
-- highlight to apply to the text.
additionalResultAttributeValue_textWithHighlightsValue :: Lens.Lens' AdditionalResultAttributeValue (Prelude.Maybe TextWithHighlights)
additionalResultAttributeValue_textWithHighlightsValue :: Lens' AdditionalResultAttributeValue (Maybe TextWithHighlights)
additionalResultAttributeValue_textWithHighlightsValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdditionalResultAttributeValue' {Maybe TextWithHighlights
textWithHighlightsValue :: Maybe TextWithHighlights
$sel:textWithHighlightsValue:AdditionalResultAttributeValue' :: AdditionalResultAttributeValue -> Maybe TextWithHighlights
textWithHighlightsValue} -> Maybe TextWithHighlights
textWithHighlightsValue) (\s :: AdditionalResultAttributeValue
s@AdditionalResultAttributeValue' {} Maybe TextWithHighlights
a -> AdditionalResultAttributeValue
s {$sel:textWithHighlightsValue:AdditionalResultAttributeValue' :: Maybe TextWithHighlights
textWithHighlightsValue = Maybe TextWithHighlights
a} :: AdditionalResultAttributeValue)

instance Data.FromJSON AdditionalResultAttributeValue where
  parseJSON :: Value -> Parser AdditionalResultAttributeValue
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AdditionalResultAttributeValue"
      ( \Object
x ->
          Maybe TextWithHighlights -> AdditionalResultAttributeValue
AdditionalResultAttributeValue'
            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
"TextWithHighlightsValue")
      )

instance
  Prelude.Hashable
    AdditionalResultAttributeValue
  where
  hashWithSalt :: Int -> AdditionalResultAttributeValue -> Int
hashWithSalt
    Int
_salt
    AdditionalResultAttributeValue' {Maybe TextWithHighlights
textWithHighlightsValue :: Maybe TextWithHighlights
$sel:textWithHighlightsValue:AdditionalResultAttributeValue' :: AdditionalResultAttributeValue -> Maybe TextWithHighlights
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TextWithHighlights
textWithHighlightsValue

instance
  Prelude.NFData
    AdditionalResultAttributeValue
  where
  rnf :: AdditionalResultAttributeValue -> ()
rnf AdditionalResultAttributeValue' {Maybe TextWithHighlights
textWithHighlightsValue :: Maybe TextWithHighlights
$sel:textWithHighlightsValue:AdditionalResultAttributeValue' :: AdditionalResultAttributeValue -> Maybe TextWithHighlights
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe TextWithHighlights
textWithHighlightsValue