module Stratosphere.Lex.Bot.BotLocaleProperty (
module Exports, BotLocaleProperty(..), mkBotLocaleProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Lex.Bot.CustomVocabularyProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.GenerativeAISettingsProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.IntentProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.SlotTypeProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.VoiceSettingsProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data BotLocaleProperty
=
BotLocaleProperty {BotLocaleProperty -> ()
haddock_workaround_ :: (),
BotLocaleProperty -> Maybe CustomVocabularyProperty
customVocabulary :: (Prelude.Maybe CustomVocabularyProperty),
BotLocaleProperty -> Maybe (Value Text)
description :: (Prelude.Maybe (Value Prelude.Text)),
BotLocaleProperty -> Maybe GenerativeAISettingsProperty
generativeAISettings :: (Prelude.Maybe GenerativeAISettingsProperty),
BotLocaleProperty -> Maybe [IntentProperty]
intents :: (Prelude.Maybe [IntentProperty]),
BotLocaleProperty -> Value Text
localeId :: (Value Prelude.Text),
BotLocaleProperty -> Value Double
nluConfidenceThreshold :: (Value Prelude.Double),
BotLocaleProperty -> Maybe [SlotTypeProperty]
slotTypes :: (Prelude.Maybe [SlotTypeProperty]),
BotLocaleProperty -> Maybe VoiceSettingsProperty
voiceSettings :: (Prelude.Maybe VoiceSettingsProperty)}
deriving stock (BotLocaleProperty -> BotLocaleProperty -> Bool
(BotLocaleProperty -> BotLocaleProperty -> Bool)
-> (BotLocaleProperty -> BotLocaleProperty -> Bool)
-> Eq BotLocaleProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BotLocaleProperty -> BotLocaleProperty -> Bool
== :: BotLocaleProperty -> BotLocaleProperty -> Bool
$c/= :: BotLocaleProperty -> BotLocaleProperty -> Bool
/= :: BotLocaleProperty -> BotLocaleProperty -> Bool
Prelude.Eq, Int -> BotLocaleProperty -> ShowS
[BotLocaleProperty] -> ShowS
BotLocaleProperty -> String
(Int -> BotLocaleProperty -> ShowS)
-> (BotLocaleProperty -> String)
-> ([BotLocaleProperty] -> ShowS)
-> Show BotLocaleProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BotLocaleProperty -> ShowS
showsPrec :: Int -> BotLocaleProperty -> ShowS
$cshow :: BotLocaleProperty -> String
show :: BotLocaleProperty -> String
$cshowList :: [BotLocaleProperty] -> ShowS
showList :: [BotLocaleProperty] -> ShowS
Prelude.Show)
mkBotLocaleProperty ::
Value Prelude.Text -> Value Prelude.Double -> BotLocaleProperty
mkBotLocaleProperty :: Value Text -> Value Double -> BotLocaleProperty
mkBotLocaleProperty Value Text
localeId Value Double
nluConfidenceThreshold
= BotLocaleProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), localeId :: Value Text
localeId = Value Text
localeId,
nluConfidenceThreshold :: Value Double
nluConfidenceThreshold = Value Double
nluConfidenceThreshold,
customVocabulary :: Maybe CustomVocabularyProperty
customVocabulary = Maybe CustomVocabularyProperty
forall a. Maybe a
Prelude.Nothing, description :: Maybe (Value Text)
description = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
generativeAISettings :: Maybe GenerativeAISettingsProperty
generativeAISettings = Maybe GenerativeAISettingsProperty
forall a. Maybe a
Prelude.Nothing, intents :: Maybe [IntentProperty]
intents = Maybe [IntentProperty]
forall a. Maybe a
Prelude.Nothing,
slotTypes :: Maybe [SlotTypeProperty]
slotTypes = Maybe [SlotTypeProperty]
forall a. Maybe a
Prelude.Nothing, voiceSettings :: Maybe VoiceSettingsProperty
voiceSettings = Maybe VoiceSettingsProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties BotLocaleProperty where
toResourceProperties :: BotLocaleProperty -> ResourceProperties
toResourceProperties BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lex::Bot.BotLocale", 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
"LocaleId" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
localeId,
Key
"NluConfidenceThreshold" 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..= Value Double
nluConfidenceThreshold]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CustomVocabularyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomVocabulary" (CustomVocabularyProperty -> (Key, Value))
-> Maybe CustomVocabularyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CustomVocabularyProperty
customVocabulary,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
Key -> GenerativeAISettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GenerativeAISettings" (GenerativeAISettingsProperty -> (Key, Value))
-> Maybe GenerativeAISettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GenerativeAISettingsProperty
generativeAISettings,
Key -> [IntentProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Intents" ([IntentProperty] -> (Key, Value))
-> Maybe [IntentProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [IntentProperty]
intents,
Key -> [SlotTypeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SlotTypes" ([SlotTypeProperty] -> (Key, Value))
-> Maybe [SlotTypeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SlotTypeProperty]
slotTypes,
Key -> VoiceSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VoiceSettings" (VoiceSettingsProperty -> (Key, Value))
-> Maybe VoiceSettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VoiceSettingsProperty
voiceSettings]))}
instance JSON.ToJSON BotLocaleProperty where
toJSON :: BotLocaleProperty -> Value
toJSON BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= [(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
"LocaleId" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
localeId,
Key
"NluConfidenceThreshold" 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..= Value Double
nluConfidenceThreshold]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CustomVocabularyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomVocabulary" (CustomVocabularyProperty -> (Key, Value))
-> Maybe CustomVocabularyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CustomVocabularyProperty
customVocabulary,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
Key -> GenerativeAISettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GenerativeAISettings" (GenerativeAISettingsProperty -> (Key, Value))
-> Maybe GenerativeAISettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GenerativeAISettingsProperty
generativeAISettings,
Key -> [IntentProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Intents" ([IntentProperty] -> (Key, Value))
-> Maybe [IntentProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [IntentProperty]
intents,
Key -> [SlotTypeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SlotTypes" ([SlotTypeProperty] -> (Key, Value))
-> Maybe [SlotTypeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SlotTypeProperty]
slotTypes,
Key -> VoiceSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VoiceSettings" (VoiceSettingsProperty -> (Key, Value))
-> Maybe VoiceSettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VoiceSettingsProperty
voiceSettings])))
instance Property "CustomVocabulary" BotLocaleProperty where
type PropertyType "CustomVocabulary" BotLocaleProperty = CustomVocabularyProperty
set :: PropertyType "CustomVocabulary" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "CustomVocabulary" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty {customVocabulary :: Maybe CustomVocabularyProperty
customVocabulary = CustomVocabularyProperty -> Maybe CustomVocabularyProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CustomVocabulary" BotLocaleProperty
CustomVocabularyProperty
newValue, Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: ()
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
instance Property "Description" BotLocaleProperty where
type PropertyType "Description" BotLocaleProperty = Value Prelude.Text
set :: PropertyType "Description" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "Description" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty {description :: Maybe (Value Text)
description = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Description" BotLocaleProperty
Value Text
newValue, Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
instance Property "GenerativeAISettings" BotLocaleProperty where
type PropertyType "GenerativeAISettings" BotLocaleProperty = GenerativeAISettingsProperty
set :: PropertyType "GenerativeAISettings" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "GenerativeAISettings" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty
{generativeAISettings :: Maybe GenerativeAISettingsProperty
generativeAISettings = GenerativeAISettingsProperty -> Maybe GenerativeAISettingsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "GenerativeAISettings" BotLocaleProperty
GenerativeAISettingsProperty
newValue, Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
instance Property "Intents" BotLocaleProperty where
type PropertyType "Intents" BotLocaleProperty = [IntentProperty]
set :: PropertyType "Intents" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "Intents" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty {intents :: Maybe [IntentProperty]
intents = [IntentProperty] -> Maybe [IntentProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [IntentProperty]
PropertyType "Intents" BotLocaleProperty
newValue, Maybe [SlotTypeProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
instance Property "LocaleId" BotLocaleProperty where
type PropertyType "LocaleId" BotLocaleProperty = Value Prelude.Text
set :: PropertyType "LocaleId" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "LocaleId" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty {localeId :: Value Text
localeId = PropertyType "LocaleId" BotLocaleProperty
Value Text
newValue, Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
instance Property "NluConfidenceThreshold" BotLocaleProperty where
type PropertyType "NluConfidenceThreshold" BotLocaleProperty = Value Prelude.Double
set :: PropertyType "NluConfidenceThreshold" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "NluConfidenceThreshold" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty {nluConfidenceThreshold :: Value Double
nluConfidenceThreshold = PropertyType "NluConfidenceThreshold" BotLocaleProperty
Value Double
newValue, Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Text
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
instance Property "SlotTypes" BotLocaleProperty where
type PropertyType "SlotTypes" BotLocaleProperty = [SlotTypeProperty]
set :: PropertyType "SlotTypes" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "SlotTypes" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty {slotTypes :: Maybe [SlotTypeProperty]
slotTypes = [SlotTypeProperty] -> Maybe [SlotTypeProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SlotTypeProperty]
PropertyType "SlotTypes" BotLocaleProperty
newValue, Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
voiceSettings :: Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
voiceSettings :: Maybe VoiceSettingsProperty
..}
instance Property "VoiceSettings" BotLocaleProperty where
type PropertyType "VoiceSettings" BotLocaleProperty = VoiceSettingsProperty
set :: PropertyType "VoiceSettings" BotLocaleProperty
-> BotLocaleProperty -> BotLocaleProperty
set PropertyType "VoiceSettings" BotLocaleProperty
newValue BotLocaleProperty {Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
Maybe VoiceSettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: BotLocaleProperty -> ()
customVocabulary :: BotLocaleProperty -> Maybe CustomVocabularyProperty
description :: BotLocaleProperty -> Maybe (Value Text)
generativeAISettings :: BotLocaleProperty -> Maybe GenerativeAISettingsProperty
intents :: BotLocaleProperty -> Maybe [IntentProperty]
localeId :: BotLocaleProperty -> Value Text
nluConfidenceThreshold :: BotLocaleProperty -> Value Double
slotTypes :: BotLocaleProperty -> Maybe [SlotTypeProperty]
voiceSettings :: BotLocaleProperty -> Maybe VoiceSettingsProperty
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
voiceSettings :: Maybe VoiceSettingsProperty
..}
= BotLocaleProperty {voiceSettings :: Maybe VoiceSettingsProperty
voiceSettings = VoiceSettingsProperty -> Maybe VoiceSettingsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "VoiceSettings" BotLocaleProperty
VoiceSettingsProperty
newValue, Maybe [SlotTypeProperty]
Maybe [IntentProperty]
Maybe (Value Text)
Maybe CustomVocabularyProperty
Maybe GenerativeAISettingsProperty
()
Value Double
Value Text
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
haddock_workaround_ :: ()
customVocabulary :: Maybe CustomVocabularyProperty
description :: Maybe (Value Text)
generativeAISettings :: Maybe GenerativeAISettingsProperty
intents :: Maybe [IntentProperty]
localeId :: Value Text
nluConfidenceThreshold :: Value Double
slotTypes :: Maybe [SlotTypeProperty]
..}