module Stratosphere.Bedrock.Flow.VectorSearchBedrockRerankingConfigurationProperty (
module Exports,
VectorSearchBedrockRerankingConfigurationProperty(..),
mkVectorSearchBedrockRerankingConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Bedrock.Flow.MetadataConfigurationForRerankingProperty as Exports
import {-# SOURCE #-} Stratosphere.Bedrock.Flow.VectorSearchBedrockRerankingModelConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data VectorSearchBedrockRerankingConfigurationProperty
=
VectorSearchBedrockRerankingConfigurationProperty {VectorSearchBedrockRerankingConfigurationProperty -> ()
haddock_workaround_ :: (),
VectorSearchBedrockRerankingConfigurationProperty
-> Maybe MetadataConfigurationForRerankingProperty
metadataConfiguration :: (Prelude.Maybe MetadataConfigurationForRerankingProperty),
VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingModelConfigurationProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty,
VectorSearchBedrockRerankingConfigurationProperty
-> Maybe (Value Double)
numberOfRerankedResults :: (Prelude.Maybe (Value Prelude.Double))}
deriving stock (VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty -> Bool
(VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty -> Bool)
-> (VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty -> Bool)
-> Eq VectorSearchBedrockRerankingConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty -> Bool
== :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty -> Bool
$c/= :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty -> Bool
/= :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty -> Bool
Prelude.Eq, Int -> VectorSearchBedrockRerankingConfigurationProperty -> ShowS
[VectorSearchBedrockRerankingConfigurationProperty] -> ShowS
VectorSearchBedrockRerankingConfigurationProperty -> String
(Int -> VectorSearchBedrockRerankingConfigurationProperty -> ShowS)
-> (VectorSearchBedrockRerankingConfigurationProperty -> String)
-> ([VectorSearchBedrockRerankingConfigurationProperty] -> ShowS)
-> Show VectorSearchBedrockRerankingConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VectorSearchBedrockRerankingConfigurationProperty -> ShowS
showsPrec :: Int -> VectorSearchBedrockRerankingConfigurationProperty -> ShowS
$cshow :: VectorSearchBedrockRerankingConfigurationProperty -> String
show :: VectorSearchBedrockRerankingConfigurationProperty -> String
$cshowList :: [VectorSearchBedrockRerankingConfigurationProperty] -> ShowS
showList :: [VectorSearchBedrockRerankingConfigurationProperty] -> ShowS
Prelude.Show)
mkVectorSearchBedrockRerankingConfigurationProperty ::
VectorSearchBedrockRerankingModelConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
mkVectorSearchBedrockRerankingConfigurationProperty :: VectorSearchBedrockRerankingModelConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
mkVectorSearchBedrockRerankingConfigurationProperty
VectorSearchBedrockRerankingModelConfigurationProperty
modelConfiguration
= VectorSearchBedrockRerankingConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
modelConfiguration = VectorSearchBedrockRerankingModelConfigurationProperty
modelConfiguration,
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
metadataConfiguration = Maybe MetadataConfigurationForRerankingProperty
forall a. Maybe a
Prelude.Nothing,
numberOfRerankedResults :: Maybe (Value Double)
numberOfRerankedResults = Maybe (Value Double)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties VectorSearchBedrockRerankingConfigurationProperty where
toResourceProperties :: VectorSearchBedrockRerankingConfigurationProperty
-> ResourceProperties
toResourceProperties
VectorSearchBedrockRerankingConfigurationProperty {Maybe (Value Double)
Maybe MetadataConfigurationForRerankingProperty
()
VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: VectorSearchBedrockRerankingConfigurationProperty -> ()
metadataConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe (Value Double)
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: Maybe (Value Double)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Bedrock::Flow.VectorSearchBedrockRerankingConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"ModelConfiguration" Key
-> VectorSearchBedrockRerankingModelConfigurationProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VectorSearchBedrockRerankingModelConfigurationProperty
modelConfiguration]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> MetadataConfigurationForRerankingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetadataConfiguration"
(MetadataConfigurationForRerankingProperty -> (Key, Value))
-> Maybe MetadataConfigurationForRerankingProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe MetadataConfigurationForRerankingProperty
metadataConfiguration,
Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NumberOfRerankedResults"
(Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
numberOfRerankedResults]))}
instance JSON.ToJSON VectorSearchBedrockRerankingConfigurationProperty where
toJSON :: VectorSearchBedrockRerankingConfigurationProperty -> Value
toJSON VectorSearchBedrockRerankingConfigurationProperty {Maybe (Value Double)
Maybe MetadataConfigurationForRerankingProperty
()
VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: VectorSearchBedrockRerankingConfigurationProperty -> ()
metadataConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe (Value Double)
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: Maybe (Value Double)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"ModelConfiguration" Key
-> VectorSearchBedrockRerankingModelConfigurationProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VectorSearchBedrockRerankingModelConfigurationProperty
modelConfiguration]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> MetadataConfigurationForRerankingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetadataConfiguration"
(MetadataConfigurationForRerankingProperty -> (Key, Value))
-> Maybe MetadataConfigurationForRerankingProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe MetadataConfigurationForRerankingProperty
metadataConfiguration,
Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NumberOfRerankedResults"
(Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
numberOfRerankedResults])))
instance Property "MetadataConfiguration" VectorSearchBedrockRerankingConfigurationProperty where
type PropertyType "MetadataConfiguration" VectorSearchBedrockRerankingConfigurationProperty = MetadataConfigurationForRerankingProperty
set :: PropertyType
"MetadataConfiguration"
VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
set PropertyType
"MetadataConfiguration"
VectorSearchBedrockRerankingConfigurationProperty
newValue VectorSearchBedrockRerankingConfigurationProperty {Maybe (Value Double)
Maybe MetadataConfigurationForRerankingProperty
()
VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: VectorSearchBedrockRerankingConfigurationProperty -> ()
metadataConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe (Value Double)
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: Maybe (Value Double)
..}
= VectorSearchBedrockRerankingConfigurationProperty
{metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
metadataConfiguration = MetadataConfigurationForRerankingProperty
-> Maybe MetadataConfigurationForRerankingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"MetadataConfiguration"
VectorSearchBedrockRerankingConfigurationProperty
MetadataConfigurationForRerankingProperty
newValue, Maybe (Value Double)
()
VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: ()
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: Maybe (Value Double)
haddock_workaround_ :: ()
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: Maybe (Value Double)
..}
instance Property "ModelConfiguration" VectorSearchBedrockRerankingConfigurationProperty where
type PropertyType "ModelConfiguration" VectorSearchBedrockRerankingConfigurationProperty = VectorSearchBedrockRerankingModelConfigurationProperty
set :: PropertyType
"ModelConfiguration"
VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
set PropertyType
"ModelConfiguration"
VectorSearchBedrockRerankingConfigurationProperty
newValue VectorSearchBedrockRerankingConfigurationProperty {Maybe (Value Double)
Maybe MetadataConfigurationForRerankingProperty
()
VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: VectorSearchBedrockRerankingConfigurationProperty -> ()
metadataConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe (Value Double)
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: Maybe (Value Double)
..}
= VectorSearchBedrockRerankingConfigurationProperty
{modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
modelConfiguration = PropertyType
"ModelConfiguration"
VectorSearchBedrockRerankingConfigurationProperty
VectorSearchBedrockRerankingModelConfigurationProperty
newValue, Maybe (Value Double)
Maybe MetadataConfigurationForRerankingProperty
()
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
numberOfRerankedResults :: Maybe (Value Double)
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
numberOfRerankedResults :: Maybe (Value Double)
..}
instance Property "NumberOfRerankedResults" VectorSearchBedrockRerankingConfigurationProperty where
type PropertyType "NumberOfRerankedResults" VectorSearchBedrockRerankingConfigurationProperty = Value Prelude.Double
set :: PropertyType
"NumberOfRerankedResults"
VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingConfigurationProperty
set PropertyType
"NumberOfRerankedResults"
VectorSearchBedrockRerankingConfigurationProperty
newValue VectorSearchBedrockRerankingConfigurationProperty {Maybe (Value Double)
Maybe MetadataConfigurationForRerankingProperty
()
VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: VectorSearchBedrockRerankingConfigurationProperty -> ()
metadataConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingConfigurationProperty
-> VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: VectorSearchBedrockRerankingConfigurationProperty
-> Maybe (Value Double)
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
numberOfRerankedResults :: Maybe (Value Double)
..}
= VectorSearchBedrockRerankingConfigurationProperty
{numberOfRerankedResults :: Maybe (Value Double)
numberOfRerankedResults = Value Double -> Maybe (Value Double)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"NumberOfRerankedResults"
VectorSearchBedrockRerankingConfigurationProperty
Value Double
newValue, Maybe MetadataConfigurationForRerankingProperty
()
VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
haddock_workaround_ :: ()
metadataConfiguration :: Maybe MetadataConfigurationForRerankingProperty
modelConfiguration :: VectorSearchBedrockRerankingModelConfigurationProperty
..}