module Stratosphere.Lex.Bot.IntentProperty (
        module Exports, IntentProperty(..), mkIntentProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Lex.Bot.BedrockAgentIntentConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.DialogCodeHookSettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.FulfillmentCodeHookSettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.InitialResponseSettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.InputContextProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.IntentClosingSettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.IntentConfirmationSettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.KendraConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.OutputContextProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.QInConnectIntentConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.QnAIntentConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.SampleUtteranceProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.SlotProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.SlotPriorityProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data IntentProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html>
    IntentProperty {IntentProperty -> ()
haddock_workaround_ :: (),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-bedrockagentintentconfiguration>
                    IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
bedrockAgentIntentConfiguration :: (Prelude.Maybe BedrockAgentIntentConfigurationProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-description>
                    IntentProperty -> Maybe (Value Text)
description :: (Prelude.Maybe (Value Prelude.Text)),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-dialogcodehook>
                    IntentProperty -> Maybe DialogCodeHookSettingProperty
dialogCodeHook :: (Prelude.Maybe DialogCodeHookSettingProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-fulfillmentcodehook>
                    IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
fulfillmentCodeHook :: (Prelude.Maybe FulfillmentCodeHookSettingProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-initialresponsesetting>
                    IntentProperty -> Maybe InitialResponseSettingProperty
initialResponseSetting :: (Prelude.Maybe InitialResponseSettingProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-inputcontexts>
                    IntentProperty -> Maybe [InputContextProperty]
inputContexts :: (Prelude.Maybe [InputContextProperty]),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-intentclosingsetting>
                    IntentProperty -> Maybe IntentClosingSettingProperty
intentClosingSetting :: (Prelude.Maybe IntentClosingSettingProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-intentconfirmationsetting>
                    IntentProperty -> Maybe IntentConfirmationSettingProperty
intentConfirmationSetting :: (Prelude.Maybe IntentConfirmationSettingProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-kendraconfiguration>
                    IntentProperty -> Maybe KendraConfigurationProperty
kendraConfiguration :: (Prelude.Maybe KendraConfigurationProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-name>
                    IntentProperty -> Value Text
name :: (Value Prelude.Text),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-outputcontexts>
                    IntentProperty -> Maybe [OutputContextProperty]
outputContexts :: (Prelude.Maybe [OutputContextProperty]),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-parentintentsignature>
                    IntentProperty -> Maybe (Value Text)
parentIntentSignature :: (Prelude.Maybe (Value Prelude.Text)),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-qinconnectintentconfiguration>
                    IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qInConnectIntentConfiguration :: (Prelude.Maybe QInConnectIntentConfigurationProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-qnaintentconfiguration>
                    IntentProperty -> Maybe QnAIntentConfigurationProperty
qnAIntentConfiguration :: (Prelude.Maybe QnAIntentConfigurationProperty),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-sampleutterances>
                    IntentProperty -> Maybe [SampleUtteranceProperty]
sampleUtterances :: (Prelude.Maybe [SampleUtteranceProperty]),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-slotpriorities>
                    IntentProperty -> Maybe [SlotPriorityProperty]
slotPriorities :: (Prelude.Maybe [SlotPriorityProperty]),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-intent.html#cfn-lex-bot-intent-slots>
                    IntentProperty -> Maybe [SlotProperty]
slots :: (Prelude.Maybe [SlotProperty])}
  deriving stock (IntentProperty -> IntentProperty -> Bool
(IntentProperty -> IntentProperty -> Bool)
-> (IntentProperty -> IntentProperty -> Bool) -> Eq IntentProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntentProperty -> IntentProperty -> Bool
== :: IntentProperty -> IntentProperty -> Bool
$c/= :: IntentProperty -> IntentProperty -> Bool
/= :: IntentProperty -> IntentProperty -> Bool
Prelude.Eq, Int -> IntentProperty -> ShowS
[IntentProperty] -> ShowS
IntentProperty -> String
(Int -> IntentProperty -> ShowS)
-> (IntentProperty -> String)
-> ([IntentProperty] -> ShowS)
-> Show IntentProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntentProperty -> ShowS
showsPrec :: Int -> IntentProperty -> ShowS
$cshow :: IntentProperty -> String
show :: IntentProperty -> String
$cshowList :: [IntentProperty] -> ShowS
showList :: [IntentProperty] -> ShowS
Prelude.Show)
mkIntentProperty :: Value Prelude.Text -> IntentProperty
mkIntentProperty :: Value Text -> IntentProperty
mkIntentProperty Value Text
name
  = IntentProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), name :: Value Text
name = Value Text
name,
       bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
bedrockAgentIntentConfiguration = Maybe BedrockAgentIntentConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       description :: Maybe (Value Text)
description = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, dialogCodeHook :: Maybe DialogCodeHookSettingProperty
dialogCodeHook = Maybe DialogCodeHookSettingProperty
forall a. Maybe a
Prelude.Nothing,
       fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
fulfillmentCodeHook = Maybe FulfillmentCodeHookSettingProperty
forall a. Maybe a
Prelude.Nothing,
       initialResponseSetting :: Maybe InitialResponseSettingProperty
initialResponseSetting = Maybe InitialResponseSettingProperty
forall a. Maybe a
Prelude.Nothing,
       inputContexts :: Maybe [InputContextProperty]
inputContexts = Maybe [InputContextProperty]
forall a. Maybe a
Prelude.Nothing,
       intentClosingSetting :: Maybe IntentClosingSettingProperty
intentClosingSetting = Maybe IntentClosingSettingProperty
forall a. Maybe a
Prelude.Nothing,
       intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
intentConfirmationSetting = Maybe IntentConfirmationSettingProperty
forall a. Maybe a
Prelude.Nothing,
       kendraConfiguration :: Maybe KendraConfigurationProperty
kendraConfiguration = Maybe KendraConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       outputContexts :: Maybe [OutputContextProperty]
outputContexts = Maybe [OutputContextProperty]
forall a. Maybe a
Prelude.Nothing,
       parentIntentSignature :: Maybe (Value Text)
parentIntentSignature = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qInConnectIntentConfiguration = Maybe QInConnectIntentConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
qnAIntentConfiguration = Maybe QnAIntentConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       sampleUtterances :: Maybe [SampleUtteranceProperty]
sampleUtterances = Maybe [SampleUtteranceProperty]
forall a. Maybe a
Prelude.Nothing,
       slotPriorities :: Maybe [SlotPriorityProperty]
slotPriorities = Maybe [SlotPriorityProperty]
forall a. Maybe a
Prelude.Nothing, slots :: Maybe [SlotProperty]
slots = Maybe [SlotProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties IntentProperty where
  toResourceProperties :: IntentProperty -> ResourceProperties
toResourceProperties IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Lex::Bot.Intent", 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
"Name" 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
name]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> BedrockAgentIntentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BedrockAgentIntentConfiguration"
                                 (BedrockAgentIntentConfigurationProperty -> (Key, Value))
-> Maybe BedrockAgentIntentConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe BedrockAgentIntentConfigurationProperty
bedrockAgentIntentConfiguration,
                               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 -> DialogCodeHookSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DialogCodeHook" (DialogCodeHookSettingProperty -> (Key, Value))
-> Maybe DialogCodeHookSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogCodeHookSettingProperty
dialogCodeHook,
                               Key -> FulfillmentCodeHookSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FulfillmentCodeHook" (FulfillmentCodeHookSettingProperty -> (Key, Value))
-> Maybe FulfillmentCodeHookSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FulfillmentCodeHookSettingProperty
fulfillmentCodeHook,
                               Key -> InitialResponseSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InitialResponseSetting"
                                 (InitialResponseSettingProperty -> (Key, Value))
-> Maybe InitialResponseSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InitialResponseSettingProperty
initialResponseSetting,
                               Key -> [InputContextProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputContexts" ([InputContextProperty] -> (Key, Value))
-> Maybe [InputContextProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InputContextProperty]
inputContexts,
                               Key -> IntentClosingSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IntentClosingSetting" (IntentClosingSettingProperty -> (Key, Value))
-> Maybe IntentClosingSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IntentClosingSettingProperty
intentClosingSetting,
                               Key -> IntentConfirmationSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IntentConfirmationSetting"
                                 (IntentConfirmationSettingProperty -> (Key, Value))
-> Maybe IntentConfirmationSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IntentConfirmationSettingProperty
intentConfirmationSetting,
                               Key -> KendraConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KendraConfiguration" (KendraConfigurationProperty -> (Key, Value))
-> Maybe KendraConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe KendraConfigurationProperty
kendraConfiguration,
                               Key -> [OutputContextProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OutputContexts" ([OutputContextProperty] -> (Key, Value))
-> Maybe [OutputContextProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [OutputContextProperty]
outputContexts,
                               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
"ParentIntentSignature"
                                 (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)
parentIntentSignature,
                               Key -> QInConnectIntentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QInConnectIntentConfiguration"
                                 (QInConnectIntentConfigurationProperty -> (Key, Value))
-> Maybe QInConnectIntentConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QInConnectIntentConfigurationProperty
qInConnectIntentConfiguration,
                               Key -> QnAIntentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QnAIntentConfiguration"
                                 (QnAIntentConfigurationProperty -> (Key, Value))
-> Maybe QnAIntentConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QnAIntentConfigurationProperty
qnAIntentConfiguration,
                               Key -> [SampleUtteranceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SampleUtterances" ([SampleUtteranceProperty] -> (Key, Value))
-> Maybe [SampleUtteranceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SampleUtteranceProperty]
sampleUtterances,
                               Key -> [SlotPriorityProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SlotPriorities" ([SlotPriorityProperty] -> (Key, Value))
-> Maybe [SlotPriorityProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SlotPriorityProperty]
slotPriorities,
                               Key -> [SlotProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Slots" ([SlotProperty] -> (Key, Value))
-> Maybe [SlotProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SlotProperty]
slots]))}
instance JSON.ToJSON IntentProperty where
  toJSON :: IntentProperty -> Value
toJSON IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = [(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
"Name" 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
name]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> BedrockAgentIntentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BedrockAgentIntentConfiguration"
                    (BedrockAgentIntentConfigurationProperty -> (Key, Value))
-> Maybe BedrockAgentIntentConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe BedrockAgentIntentConfigurationProperty
bedrockAgentIntentConfiguration,
                  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 -> DialogCodeHookSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DialogCodeHook" (DialogCodeHookSettingProperty -> (Key, Value))
-> Maybe DialogCodeHookSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogCodeHookSettingProperty
dialogCodeHook,
                  Key -> FulfillmentCodeHookSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FulfillmentCodeHook" (FulfillmentCodeHookSettingProperty -> (Key, Value))
-> Maybe FulfillmentCodeHookSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FulfillmentCodeHookSettingProperty
fulfillmentCodeHook,
                  Key -> InitialResponseSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InitialResponseSetting"
                    (InitialResponseSettingProperty -> (Key, Value))
-> Maybe InitialResponseSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InitialResponseSettingProperty
initialResponseSetting,
                  Key -> [InputContextProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputContexts" ([InputContextProperty] -> (Key, Value))
-> Maybe [InputContextProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InputContextProperty]
inputContexts,
                  Key -> IntentClosingSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IntentClosingSetting" (IntentClosingSettingProperty -> (Key, Value))
-> Maybe IntentClosingSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IntentClosingSettingProperty
intentClosingSetting,
                  Key -> IntentConfirmationSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IntentConfirmationSetting"
                    (IntentConfirmationSettingProperty -> (Key, Value))
-> Maybe IntentConfirmationSettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IntentConfirmationSettingProperty
intentConfirmationSetting,
                  Key -> KendraConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KendraConfiguration" (KendraConfigurationProperty -> (Key, Value))
-> Maybe KendraConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe KendraConfigurationProperty
kendraConfiguration,
                  Key -> [OutputContextProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OutputContexts" ([OutputContextProperty] -> (Key, Value))
-> Maybe [OutputContextProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [OutputContextProperty]
outputContexts,
                  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
"ParentIntentSignature"
                    (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)
parentIntentSignature,
                  Key -> QInConnectIntentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QInConnectIntentConfiguration"
                    (QInConnectIntentConfigurationProperty -> (Key, Value))
-> Maybe QInConnectIntentConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QInConnectIntentConfigurationProperty
qInConnectIntentConfiguration,
                  Key -> QnAIntentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QnAIntentConfiguration"
                    (QnAIntentConfigurationProperty -> (Key, Value))
-> Maybe QnAIntentConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QnAIntentConfigurationProperty
qnAIntentConfiguration,
                  Key -> [SampleUtteranceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SampleUtterances" ([SampleUtteranceProperty] -> (Key, Value))
-> Maybe [SampleUtteranceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SampleUtteranceProperty]
sampleUtterances,
                  Key -> [SlotPriorityProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SlotPriorities" ([SlotPriorityProperty] -> (Key, Value))
-> Maybe [SlotPriorityProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SlotPriorityProperty]
slotPriorities,
                  Key -> [SlotProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Slots" ([SlotProperty] -> (Key, Value))
-> Maybe [SlotProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SlotProperty]
slots])))
instance Property "BedrockAgentIntentConfiguration" IntentProperty where
  type PropertyType "BedrockAgentIntentConfiguration" IntentProperty = BedrockAgentIntentConfigurationProperty
  set :: PropertyType "BedrockAgentIntentConfiguration" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "BedrockAgentIntentConfiguration" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty
        {bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
bedrockAgentIntentConfiguration = BedrockAgentIntentConfigurationProperty
-> Maybe BedrockAgentIntentConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BedrockAgentIntentConfiguration" IntentProperty
BedrockAgentIntentConfigurationProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "Description" IntentProperty where
  type PropertyType "Description" IntentProperty = Value Prelude.Text
  set :: PropertyType "Description" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "Description" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {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" IntentProperty
Value Text
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "DialogCodeHook" IntentProperty where
  type PropertyType "DialogCodeHook" IntentProperty = DialogCodeHookSettingProperty
  set :: PropertyType "DialogCodeHook" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "DialogCodeHook" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {dialogCodeHook :: Maybe DialogCodeHookSettingProperty
dialogCodeHook = DialogCodeHookSettingProperty
-> Maybe DialogCodeHookSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DialogCodeHook" IntentProperty
DialogCodeHookSettingProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "FulfillmentCodeHook" IntentProperty where
  type PropertyType "FulfillmentCodeHook" IntentProperty = FulfillmentCodeHookSettingProperty
  set :: PropertyType "FulfillmentCodeHook" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "FulfillmentCodeHook" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
fulfillmentCodeHook = FulfillmentCodeHookSettingProperty
-> Maybe FulfillmentCodeHookSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FulfillmentCodeHook" IntentProperty
FulfillmentCodeHookSettingProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "InitialResponseSetting" IntentProperty where
  type PropertyType "InitialResponseSetting" IntentProperty = InitialResponseSettingProperty
  set :: PropertyType "InitialResponseSetting" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "InitialResponseSetting" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty
        {initialResponseSetting :: Maybe InitialResponseSettingProperty
initialResponseSetting = InitialResponseSettingProperty
-> Maybe InitialResponseSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InitialResponseSetting" IntentProperty
InitialResponseSettingProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "InputContexts" IntentProperty where
  type PropertyType "InputContexts" IntentProperty = [InputContextProperty]
  set :: PropertyType "InputContexts" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "InputContexts" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {inputContexts :: Maybe [InputContextProperty]
inputContexts = [InputContextProperty] -> Maybe [InputContextProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [InputContextProperty]
PropertyType "InputContexts" IntentProperty
newValue, Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "IntentClosingSetting" IntentProperty where
  type PropertyType "IntentClosingSetting" IntentProperty = IntentClosingSettingProperty
  set :: PropertyType "IntentClosingSetting" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "IntentClosingSetting" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {intentClosingSetting :: Maybe IntentClosingSettingProperty
intentClosingSetting = IntentClosingSettingProperty -> Maybe IntentClosingSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IntentClosingSetting" IntentProperty
IntentClosingSettingProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "IntentConfirmationSetting" IntentProperty where
  type PropertyType "IntentConfirmationSetting" IntentProperty = IntentConfirmationSettingProperty
  set :: PropertyType "IntentConfirmationSetting" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "IntentConfirmationSetting" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty
        {intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
intentConfirmationSetting = IntentConfirmationSettingProperty
-> Maybe IntentConfirmationSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IntentConfirmationSetting" IntentProperty
IntentConfirmationSettingProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "KendraConfiguration" IntentProperty where
  type PropertyType "KendraConfiguration" IntentProperty = KendraConfigurationProperty
  set :: PropertyType "KendraConfiguration" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "KendraConfiguration" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {kendraConfiguration :: Maybe KendraConfigurationProperty
kendraConfiguration = KendraConfigurationProperty -> Maybe KendraConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "KendraConfiguration" IntentProperty
KendraConfigurationProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "Name" IntentProperty where
  type PropertyType "Name" IntentProperty = Value Prelude.Text
  set :: PropertyType "Name" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "Name" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {name :: Value Text
name = PropertyType "Name" IntentProperty
Value Text
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "OutputContexts" IntentProperty where
  type PropertyType "OutputContexts" IntentProperty = [OutputContextProperty]
  set :: PropertyType "OutputContexts" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "OutputContexts" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {outputContexts :: Maybe [OutputContextProperty]
outputContexts = [OutputContextProperty] -> Maybe [OutputContextProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [OutputContextProperty]
PropertyType "OutputContexts" IntentProperty
newValue, Maybe [InputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "ParentIntentSignature" IntentProperty where
  type PropertyType "ParentIntentSignature" IntentProperty = Value Prelude.Text
  set :: PropertyType "ParentIntentSignature" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "ParentIntentSignature" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty
        {parentIntentSignature :: Maybe (Value Text)
parentIntentSignature = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ParentIntentSignature" IntentProperty
Value Text
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "QInConnectIntentConfiguration" IntentProperty where
  type PropertyType "QInConnectIntentConfiguration" IntentProperty = QInConnectIntentConfigurationProperty
  set :: PropertyType "QInConnectIntentConfiguration" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "QInConnectIntentConfiguration" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty
        {qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qInConnectIntentConfiguration = QInConnectIntentConfigurationProperty
-> Maybe QInConnectIntentConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "QInConnectIntentConfiguration" IntentProperty
QInConnectIntentConfigurationProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "QnAIntentConfiguration" IntentProperty where
  type PropertyType "QnAIntentConfiguration" IntentProperty = QnAIntentConfigurationProperty
  set :: PropertyType "QnAIntentConfiguration" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "QnAIntentConfiguration" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty
        {qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
qnAIntentConfiguration = QnAIntentConfigurationProperty
-> Maybe QnAIntentConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "QnAIntentConfiguration" IntentProperty
QnAIntentConfigurationProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "SampleUtterances" IntentProperty where
  type PropertyType "SampleUtterances" IntentProperty = [SampleUtteranceProperty]
  set :: PropertyType "SampleUtterances" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "SampleUtterances" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {sampleUtterances :: Maybe [SampleUtteranceProperty]
sampleUtterances = [SampleUtteranceProperty] -> Maybe [SampleUtteranceProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SampleUtteranceProperty]
PropertyType "SampleUtterances" IntentProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "SlotPriorities" IntentProperty where
  type PropertyType "SlotPriorities" IntentProperty = [SlotPriorityProperty]
  set :: PropertyType "SlotPriorities" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "SlotPriorities" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {slotPriorities :: Maybe [SlotPriorityProperty]
slotPriorities = [SlotPriorityProperty] -> Maybe [SlotPriorityProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SlotPriorityProperty]
PropertyType "SlotPriorities" IntentProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slots :: Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slots :: Maybe [SlotProperty]
..}
instance Property "Slots" IntentProperty where
  type PropertyType "Slots" IntentProperty = [SlotProperty]
  set :: PropertyType "Slots" IntentProperty
-> IntentProperty -> IntentProperty
set PropertyType "Slots" IntentProperty
newValue IntentProperty {Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe [SlotProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: IntentProperty -> ()
bedrockAgentIntentConfiguration :: IntentProperty -> Maybe BedrockAgentIntentConfigurationProperty
description :: IntentProperty -> Maybe (Value Text)
dialogCodeHook :: IntentProperty -> Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: IntentProperty -> Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: IntentProperty -> Maybe InitialResponseSettingProperty
inputContexts :: IntentProperty -> Maybe [InputContextProperty]
intentClosingSetting :: IntentProperty -> Maybe IntentClosingSettingProperty
intentConfirmationSetting :: IntentProperty -> Maybe IntentConfirmationSettingProperty
kendraConfiguration :: IntentProperty -> Maybe KendraConfigurationProperty
name :: IntentProperty -> Value Text
outputContexts :: IntentProperty -> Maybe [OutputContextProperty]
parentIntentSignature :: IntentProperty -> Maybe (Value Text)
qInConnectIntentConfiguration :: IntentProperty -> Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: IntentProperty -> Maybe QnAIntentConfigurationProperty
sampleUtterances :: IntentProperty -> Maybe [SampleUtteranceProperty]
slotPriorities :: IntentProperty -> Maybe [SlotPriorityProperty]
slots :: IntentProperty -> Maybe [SlotProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
slots :: Maybe [SlotProperty]
..}
    = IntentProperty {slots :: Maybe [SlotProperty]
slots = [SlotProperty] -> Maybe [SlotProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SlotProperty]
PropertyType "Slots" IntentProperty
newValue, Maybe [InputContextProperty]
Maybe [OutputContextProperty]
Maybe [SampleUtteranceProperty]
Maybe [SlotPriorityProperty]
Maybe (Value Text)
Maybe BedrockAgentIntentConfigurationProperty
Maybe DialogCodeHookSettingProperty
Maybe KendraConfigurationProperty
Maybe QInConnectIntentConfigurationProperty
Maybe QnAIntentConfigurationProperty
Maybe FulfillmentCodeHookSettingProperty
Maybe IntentClosingSettingProperty
Maybe InitialResponseSettingProperty
Maybe IntentConfirmationSettingProperty
()
Value Text
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
haddock_workaround_ :: ()
bedrockAgentIntentConfiguration :: Maybe BedrockAgentIntentConfigurationProperty
description :: Maybe (Value Text)
dialogCodeHook :: Maybe DialogCodeHookSettingProperty
fulfillmentCodeHook :: Maybe FulfillmentCodeHookSettingProperty
initialResponseSetting :: Maybe InitialResponseSettingProperty
inputContexts :: Maybe [InputContextProperty]
intentClosingSetting :: Maybe IntentClosingSettingProperty
intentConfirmationSetting :: Maybe IntentConfirmationSettingProperty
kendraConfiguration :: Maybe KendraConfigurationProperty
name :: Value Text
outputContexts :: Maybe [OutputContextProperty]
parentIntentSignature :: Maybe (Value Text)
qInConnectIntentConfiguration :: Maybe QInConnectIntentConfigurationProperty
qnAIntentConfiguration :: Maybe QnAIntentConfigurationProperty
sampleUtterances :: Maybe [SampleUtteranceProperty]
slotPriorities :: Maybe [SlotPriorityProperty]
..}