module Stratosphere.Bedrock.DataSource.HierarchicalChunkingConfigurationProperty (
module Exports, HierarchicalChunkingConfigurationProperty(..),
mkHierarchicalChunkingConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Bedrock.DataSource.HierarchicalChunkingLevelConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data HierarchicalChunkingConfigurationProperty
=
HierarchicalChunkingConfigurationProperty {HierarchicalChunkingConfigurationProperty -> ()
haddock_workaround_ :: (),
HierarchicalChunkingConfigurationProperty
-> [HierarchicalChunkingLevelConfigurationProperty]
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty],
HierarchicalChunkingConfigurationProperty -> Value Integer
overlapTokens :: (Value Prelude.Integer)}
deriving stock (HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty -> Bool
(HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty -> Bool)
-> (HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty -> Bool)
-> Eq HierarchicalChunkingConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty -> Bool
== :: HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty -> Bool
$c/= :: HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty -> Bool
/= :: HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty -> Bool
Prelude.Eq, Int -> HierarchicalChunkingConfigurationProperty -> ShowS
[HierarchicalChunkingConfigurationProperty] -> ShowS
HierarchicalChunkingConfigurationProperty -> String
(Int -> HierarchicalChunkingConfigurationProperty -> ShowS)
-> (HierarchicalChunkingConfigurationProperty -> String)
-> ([HierarchicalChunkingConfigurationProperty] -> ShowS)
-> Show HierarchicalChunkingConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HierarchicalChunkingConfigurationProperty -> ShowS
showsPrec :: Int -> HierarchicalChunkingConfigurationProperty -> ShowS
$cshow :: HierarchicalChunkingConfigurationProperty -> String
show :: HierarchicalChunkingConfigurationProperty -> String
$cshowList :: [HierarchicalChunkingConfigurationProperty] -> ShowS
showList :: [HierarchicalChunkingConfigurationProperty] -> ShowS
Prelude.Show)
mkHierarchicalChunkingConfigurationProperty ::
[HierarchicalChunkingLevelConfigurationProperty]
-> Value Prelude.Integer
-> HierarchicalChunkingConfigurationProperty
mkHierarchicalChunkingConfigurationProperty :: [HierarchicalChunkingLevelConfigurationProperty]
-> Value Integer -> HierarchicalChunkingConfigurationProperty
mkHierarchicalChunkingConfigurationProperty
[HierarchicalChunkingLevelConfigurationProperty]
levelConfigurations
Value Integer
overlapTokens
= HierarchicalChunkingConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (),
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
levelConfigurations = [HierarchicalChunkingLevelConfigurationProperty]
levelConfigurations,
overlapTokens :: Value Integer
overlapTokens = Value Integer
overlapTokens}
instance ToResourceProperties HierarchicalChunkingConfigurationProperty where
toResourceProperties :: HierarchicalChunkingConfigurationProperty -> ResourceProperties
toResourceProperties HierarchicalChunkingConfigurationProperty {[HierarchicalChunkingLevelConfigurationProperty]
()
Value Integer
haddock_workaround_ :: HierarchicalChunkingConfigurationProperty -> ()
levelConfigurations :: HierarchicalChunkingConfigurationProperty
-> [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: HierarchicalChunkingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: Value Integer
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Bedrock::DataSource.HierarchicalChunkingConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"LevelConfigurations" Key
-> [HierarchicalChunkingLevelConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [HierarchicalChunkingLevelConfigurationProperty]
levelConfigurations,
Key
"OverlapTokens" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
overlapTokens]}
instance JSON.ToJSON HierarchicalChunkingConfigurationProperty where
toJSON :: HierarchicalChunkingConfigurationProperty -> Value
toJSON HierarchicalChunkingConfigurationProperty {[HierarchicalChunkingLevelConfigurationProperty]
()
Value Integer
haddock_workaround_ :: HierarchicalChunkingConfigurationProperty -> ()
levelConfigurations :: HierarchicalChunkingConfigurationProperty
-> [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: HierarchicalChunkingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: Value Integer
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"LevelConfigurations" Key
-> [HierarchicalChunkingLevelConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [HierarchicalChunkingLevelConfigurationProperty]
levelConfigurations,
Key
"OverlapTokens" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
overlapTokens]
instance Property "LevelConfigurations" HierarchicalChunkingConfigurationProperty where
type PropertyType "LevelConfigurations" HierarchicalChunkingConfigurationProperty = [HierarchicalChunkingLevelConfigurationProperty]
set :: PropertyType
"LevelConfigurations" HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty
set PropertyType
"LevelConfigurations" HierarchicalChunkingConfigurationProperty
newValue HierarchicalChunkingConfigurationProperty {[HierarchicalChunkingLevelConfigurationProperty]
()
Value Integer
haddock_workaround_ :: HierarchicalChunkingConfigurationProperty -> ()
levelConfigurations :: HierarchicalChunkingConfigurationProperty
-> [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: HierarchicalChunkingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: Value Integer
..}
= HierarchicalChunkingConfigurationProperty
{levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
levelConfigurations = [HierarchicalChunkingLevelConfigurationProperty]
PropertyType
"LevelConfigurations" HierarchicalChunkingConfigurationProperty
newValue, ()
Value Integer
haddock_workaround_ :: ()
overlapTokens :: Value Integer
haddock_workaround_ :: ()
overlapTokens :: Value Integer
..}
instance Property "OverlapTokens" HierarchicalChunkingConfigurationProperty where
type PropertyType "OverlapTokens" HierarchicalChunkingConfigurationProperty = Value Prelude.Integer
set :: PropertyType
"OverlapTokens" HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty
-> HierarchicalChunkingConfigurationProperty
set PropertyType
"OverlapTokens" HierarchicalChunkingConfigurationProperty
newValue HierarchicalChunkingConfigurationProperty {[HierarchicalChunkingLevelConfigurationProperty]
()
Value Integer
haddock_workaround_ :: HierarchicalChunkingConfigurationProperty -> ()
levelConfigurations :: HierarchicalChunkingConfigurationProperty
-> [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: HierarchicalChunkingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
overlapTokens :: Value Integer
..}
= HierarchicalChunkingConfigurationProperty
{overlapTokens :: Value Integer
overlapTokens = PropertyType
"OverlapTokens" HierarchicalChunkingConfigurationProperty
Value Integer
newValue, [HierarchicalChunkingLevelConfigurationProperty]
()
haddock_workaround_ :: ()
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
haddock_workaround_ :: ()
levelConfigurations :: [HierarchicalChunkingLevelConfigurationProperty]
..}