module Stratosphere.Lex.Bot.IntentConfirmationSettingProperty (
module Exports, IntentConfirmationSettingProperty(..),
mkIntentConfirmationSettingProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Lex.Bot.ConditionalSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.DialogCodeHookInvocationSettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.DialogStateProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.ElicitationCodeHookInvocationSettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.PromptSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.ResponseSpecificationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data IntentConfirmationSettingProperty
=
IntentConfirmationSettingProperty {IntentConfirmationSettingProperty -> ()
haddock_workaround_ :: (),
IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
codeHook :: (Prelude.Maybe DialogCodeHookInvocationSettingProperty),
IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationConditional :: (Prelude.Maybe ConditionalSpecificationProperty),
IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationNextStep :: (Prelude.Maybe DialogStateProperty),
IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
confirmationResponse :: (Prelude.Maybe ResponseSpecificationProperty),
IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationConditional :: (Prelude.Maybe ConditionalSpecificationProperty),
IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationNextStep :: (Prelude.Maybe DialogStateProperty),
IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationResponse :: (Prelude.Maybe ResponseSpecificationProperty),
IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
elicitationCodeHook :: (Prelude.Maybe ElicitationCodeHookInvocationSettingProperty),
IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureConditional :: (Prelude.Maybe ConditionalSpecificationProperty),
IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureNextStep :: (Prelude.Maybe DialogStateProperty),
IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
failureResponse :: (Prelude.Maybe ResponseSpecificationProperty),
IntentConfirmationSettingProperty -> Maybe (Value Bool)
isActive :: (Prelude.Maybe (Value Prelude.Bool)),
IntentConfirmationSettingProperty -> PromptSpecificationProperty
promptSpecification :: PromptSpecificationProperty}
deriving stock (IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty -> Bool
(IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty -> Bool)
-> (IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty -> Bool)
-> Eq IntentConfirmationSettingProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty -> Bool
== :: IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty -> Bool
$c/= :: IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty -> Bool
/= :: IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty -> Bool
Prelude.Eq, Int -> IntentConfirmationSettingProperty -> ShowS
[IntentConfirmationSettingProperty] -> ShowS
IntentConfirmationSettingProperty -> String
(Int -> IntentConfirmationSettingProperty -> ShowS)
-> (IntentConfirmationSettingProperty -> String)
-> ([IntentConfirmationSettingProperty] -> ShowS)
-> Show IntentConfirmationSettingProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntentConfirmationSettingProperty -> ShowS
showsPrec :: Int -> IntentConfirmationSettingProperty -> ShowS
$cshow :: IntentConfirmationSettingProperty -> String
show :: IntentConfirmationSettingProperty -> String
$cshowList :: [IntentConfirmationSettingProperty] -> ShowS
showList :: [IntentConfirmationSettingProperty] -> ShowS
Prelude.Show)
mkIntentConfirmationSettingProperty ::
PromptSpecificationProperty -> IntentConfirmationSettingProperty
mkIntentConfirmationSettingProperty :: PromptSpecificationProperty -> IntentConfirmationSettingProperty
mkIntentConfirmationSettingProperty PromptSpecificationProperty
promptSpecification
= IntentConfirmationSettingProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (),
promptSpecification :: PromptSpecificationProperty
promptSpecification = PromptSpecificationProperty
promptSpecification,
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
codeHook = Maybe DialogCodeHookInvocationSettingProperty
forall a. Maybe a
Prelude.Nothing,
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationConditional = Maybe ConditionalSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
confirmationNextStep :: Maybe DialogStateProperty
confirmationNextStep = Maybe DialogStateProperty
forall a. Maybe a
Prelude.Nothing,
confirmationResponse :: Maybe ResponseSpecificationProperty
confirmationResponse = Maybe ResponseSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationConditional = Maybe ConditionalSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
declinationNextStep :: Maybe DialogStateProperty
declinationNextStep = Maybe DialogStateProperty
forall a. Maybe a
Prelude.Nothing,
declinationResponse :: Maybe ResponseSpecificationProperty
declinationResponse = Maybe ResponseSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
elicitationCodeHook = Maybe ElicitationCodeHookInvocationSettingProperty
forall a. Maybe a
Prelude.Nothing,
failureConditional :: Maybe ConditionalSpecificationProperty
failureConditional = Maybe ConditionalSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
failureNextStep :: Maybe DialogStateProperty
failureNextStep = Maybe DialogStateProperty
forall a. Maybe a
Prelude.Nothing,
failureResponse :: Maybe ResponseSpecificationProperty
failureResponse = Maybe ResponseSpecificationProperty
forall a. Maybe a
Prelude.Nothing, isActive :: Maybe (Value Bool)
isActive = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties IntentConfirmationSettingProperty where
toResourceProperties :: IntentConfirmationSettingProperty -> ResourceProperties
toResourceProperties IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lex::Bot.IntentConfirmationSetting",
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
"PromptSpecification" Key -> PromptSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= PromptSpecificationProperty
promptSpecification]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> DialogCodeHookInvocationSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CodeHook" (DialogCodeHookInvocationSettingProperty -> (Key, Value))
-> Maybe DialogCodeHookInvocationSettingProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogCodeHookInvocationSettingProperty
codeHook,
Key -> ConditionalSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfirmationConditional"
(ConditionalSpecificationProperty -> (Key, Value))
-> Maybe ConditionalSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConditionalSpecificationProperty
confirmationConditional,
Key -> DialogStateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfirmationNextStep" (DialogStateProperty -> (Key, Value))
-> Maybe DialogStateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogStateProperty
confirmationNextStep,
Key -> ResponseSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfirmationResponse" (ResponseSpecificationProperty -> (Key, Value))
-> Maybe ResponseSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResponseSpecificationProperty
confirmationResponse,
Key -> ConditionalSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeclinationConditional"
(ConditionalSpecificationProperty -> (Key, Value))
-> Maybe ConditionalSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConditionalSpecificationProperty
declinationConditional,
Key -> DialogStateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeclinationNextStep" (DialogStateProperty -> (Key, Value))
-> Maybe DialogStateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogStateProperty
declinationNextStep,
Key -> ResponseSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeclinationResponse" (ResponseSpecificationProperty -> (Key, Value))
-> Maybe ResponseSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResponseSpecificationProperty
declinationResponse,
Key -> ElicitationCodeHookInvocationSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElicitationCodeHook" (ElicitationCodeHookInvocationSettingProperty -> (Key, Value))
-> Maybe ElicitationCodeHookInvocationSettingProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ElicitationCodeHookInvocationSettingProperty
elicitationCodeHook,
Key -> ConditionalSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FailureConditional" (ConditionalSpecificationProperty -> (Key, Value))
-> Maybe ConditionalSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConditionalSpecificationProperty
failureConditional,
Key -> DialogStateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FailureNextStep" (DialogStateProperty -> (Key, Value))
-> Maybe DialogStateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogStateProperty
failureNextStep,
Key -> ResponseSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FailureResponse" (ResponseSpecificationProperty -> (Key, Value))
-> Maybe ResponseSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResponseSpecificationProperty
failureResponse,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IsActive" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
isActive]))}
instance JSON.ToJSON IntentConfirmationSettingProperty where
toJSON :: IntentConfirmationSettingProperty -> Value
toJSON IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= [(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
"PromptSpecification" Key -> PromptSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= PromptSpecificationProperty
promptSpecification]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> DialogCodeHookInvocationSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CodeHook" (DialogCodeHookInvocationSettingProperty -> (Key, Value))
-> Maybe DialogCodeHookInvocationSettingProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogCodeHookInvocationSettingProperty
codeHook,
Key -> ConditionalSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfirmationConditional"
(ConditionalSpecificationProperty -> (Key, Value))
-> Maybe ConditionalSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConditionalSpecificationProperty
confirmationConditional,
Key -> DialogStateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfirmationNextStep" (DialogStateProperty -> (Key, Value))
-> Maybe DialogStateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogStateProperty
confirmationNextStep,
Key -> ResponseSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfirmationResponse" (ResponseSpecificationProperty -> (Key, Value))
-> Maybe ResponseSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResponseSpecificationProperty
confirmationResponse,
Key -> ConditionalSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeclinationConditional"
(ConditionalSpecificationProperty -> (Key, Value))
-> Maybe ConditionalSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConditionalSpecificationProperty
declinationConditional,
Key -> DialogStateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeclinationNextStep" (DialogStateProperty -> (Key, Value))
-> Maybe DialogStateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogStateProperty
declinationNextStep,
Key -> ResponseSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeclinationResponse" (ResponseSpecificationProperty -> (Key, Value))
-> Maybe ResponseSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResponseSpecificationProperty
declinationResponse,
Key -> ElicitationCodeHookInvocationSettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElicitationCodeHook" (ElicitationCodeHookInvocationSettingProperty -> (Key, Value))
-> Maybe ElicitationCodeHookInvocationSettingProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ElicitationCodeHookInvocationSettingProperty
elicitationCodeHook,
Key -> ConditionalSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FailureConditional" (ConditionalSpecificationProperty -> (Key, Value))
-> Maybe ConditionalSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConditionalSpecificationProperty
failureConditional,
Key -> DialogStateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FailureNextStep" (DialogStateProperty -> (Key, Value))
-> Maybe DialogStateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogStateProperty
failureNextStep,
Key -> ResponseSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FailureResponse" (ResponseSpecificationProperty -> (Key, Value))
-> Maybe ResponseSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResponseSpecificationProperty
failureResponse,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IsActive" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
isActive])))
instance Property "CodeHook" IntentConfirmationSettingProperty where
type PropertyType "CodeHook" IntentConfirmationSettingProperty = DialogCodeHookInvocationSettingProperty
set :: PropertyType "CodeHook" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType "CodeHook" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{codeHook :: Maybe DialogCodeHookInvocationSettingProperty
codeHook = DialogCodeHookInvocationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CodeHook" IntentConfirmationSettingProperty
DialogCodeHookInvocationSettingProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "ConfirmationConditional" IntentConfirmationSettingProperty where
type PropertyType "ConfirmationConditional" IntentConfirmationSettingProperty = ConditionalSpecificationProperty
set :: PropertyType
"ConfirmationConditional" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"ConfirmationConditional" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationConditional = ConditionalSpecificationProperty
-> Maybe ConditionalSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"ConfirmationConditional" IntentConfirmationSettingProperty
ConditionalSpecificationProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "ConfirmationNextStep" IntentConfirmationSettingProperty where
type PropertyType "ConfirmationNextStep" IntentConfirmationSettingProperty = DialogStateProperty
set :: PropertyType
"ConfirmationNextStep" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"ConfirmationNextStep" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{confirmationNextStep :: Maybe DialogStateProperty
confirmationNextStep = DialogStateProperty -> Maybe DialogStateProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"ConfirmationNextStep" IntentConfirmationSettingProperty
DialogStateProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "ConfirmationResponse" IntentConfirmationSettingProperty where
type PropertyType "ConfirmationResponse" IntentConfirmationSettingProperty = ResponseSpecificationProperty
set :: PropertyType
"ConfirmationResponse" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"ConfirmationResponse" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{confirmationResponse :: Maybe ResponseSpecificationProperty
confirmationResponse = ResponseSpecificationProperty
-> Maybe ResponseSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"ConfirmationResponse" IntentConfirmationSettingProperty
ResponseSpecificationProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "DeclinationConditional" IntentConfirmationSettingProperty where
type PropertyType "DeclinationConditional" IntentConfirmationSettingProperty = ConditionalSpecificationProperty
set :: PropertyType
"DeclinationConditional" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"DeclinationConditional" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{declinationConditional :: Maybe ConditionalSpecificationProperty
declinationConditional = ConditionalSpecificationProperty
-> Maybe ConditionalSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"DeclinationConditional" IntentConfirmationSettingProperty
ConditionalSpecificationProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "DeclinationNextStep" IntentConfirmationSettingProperty where
type PropertyType "DeclinationNextStep" IntentConfirmationSettingProperty = DialogStateProperty
set :: PropertyType
"DeclinationNextStep" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"DeclinationNextStep" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{declinationNextStep :: Maybe DialogStateProperty
declinationNextStep = DialogStateProperty -> Maybe DialogStateProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"DeclinationNextStep" IntentConfirmationSettingProperty
DialogStateProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "DeclinationResponse" IntentConfirmationSettingProperty where
type PropertyType "DeclinationResponse" IntentConfirmationSettingProperty = ResponseSpecificationProperty
set :: PropertyType
"DeclinationResponse" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"DeclinationResponse" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{declinationResponse :: Maybe ResponseSpecificationProperty
declinationResponse = ResponseSpecificationProperty
-> Maybe ResponseSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"DeclinationResponse" IntentConfirmationSettingProperty
ResponseSpecificationProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "ElicitationCodeHook" IntentConfirmationSettingProperty where
type PropertyType "ElicitationCodeHook" IntentConfirmationSettingProperty = ElicitationCodeHookInvocationSettingProperty
set :: PropertyType
"ElicitationCodeHook" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"ElicitationCodeHook" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
elicitationCodeHook = ElicitationCodeHookInvocationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"ElicitationCodeHook" IntentConfirmationSettingProperty
ElicitationCodeHookInvocationSettingProperty
newValue, Maybe (Value Bool)
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "FailureConditional" IntentConfirmationSettingProperty where
type PropertyType "FailureConditional" IntentConfirmationSettingProperty = ConditionalSpecificationProperty
set :: PropertyType "FailureConditional" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType "FailureConditional" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{failureConditional :: Maybe ConditionalSpecificationProperty
failureConditional = ConditionalSpecificationProperty
-> Maybe ConditionalSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FailureConditional" IntentConfirmationSettingProperty
ConditionalSpecificationProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "FailureNextStep" IntentConfirmationSettingProperty where
type PropertyType "FailureNextStep" IntentConfirmationSettingProperty = DialogStateProperty
set :: PropertyType "FailureNextStep" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType "FailureNextStep" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{failureNextStep :: Maybe DialogStateProperty
failureNextStep = DialogStateProperty -> Maybe DialogStateProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FailureNextStep" IntentConfirmationSettingProperty
DialogStateProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "FailureResponse" IntentConfirmationSettingProperty where
type PropertyType "FailureResponse" IntentConfirmationSettingProperty = ResponseSpecificationProperty
set :: PropertyType "FailureResponse" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType "FailureResponse" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{failureResponse :: Maybe ResponseSpecificationProperty
failureResponse = ResponseSpecificationProperty
-> Maybe ResponseSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FailureResponse" IntentConfirmationSettingProperty
ResponseSpecificationProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
instance Property "IsActive" IntentConfirmationSettingProperty where
type PropertyType "IsActive" IntentConfirmationSettingProperty = Value Prelude.Bool
set :: PropertyType "IsActive" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType "IsActive" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{isActive :: Maybe (Value Bool)
isActive = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IsActive" IntentConfirmationSettingProperty
Value Bool
newValue, Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
promptSpecification :: PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
promptSpecification :: PromptSpecificationProperty
..}
instance Property "PromptSpecification" IntentConfirmationSettingProperty where
type PropertyType "PromptSpecification" IntentConfirmationSettingProperty = PromptSpecificationProperty
set :: PropertyType
"PromptSpecification" IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
-> IntentConfirmationSettingProperty
set PropertyType
"PromptSpecification" IntentConfirmationSettingProperty
newValue IntentConfirmationSettingProperty {Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
PromptSpecificationProperty
haddock_workaround_ :: IntentConfirmationSettingProperty -> ()
codeHook :: IntentConfirmationSettingProperty
-> Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
confirmationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
confirmationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
declinationConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
declinationNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
declinationResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
elicitationCodeHook :: IntentConfirmationSettingProperty
-> Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: IntentConfirmationSettingProperty
-> Maybe ConditionalSpecificationProperty
failureNextStep :: IntentConfirmationSettingProperty -> Maybe DialogStateProperty
failureResponse :: IntentConfirmationSettingProperty
-> Maybe ResponseSpecificationProperty
isActive :: IntentConfirmationSettingProperty -> Maybe (Value Bool)
promptSpecification :: IntentConfirmationSettingProperty -> PromptSpecificationProperty
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
promptSpecification :: PromptSpecificationProperty
..}
= IntentConfirmationSettingProperty
{promptSpecification :: PromptSpecificationProperty
promptSpecification = PropertyType
"PromptSpecification" IntentConfirmationSettingProperty
PromptSpecificationProperty
newValue, Maybe (Value Bool)
Maybe ElicitationCodeHookInvocationSettingProperty
Maybe ResponseSpecificationProperty
Maybe DialogStateProperty
Maybe ConditionalSpecificationProperty
Maybe DialogCodeHookInvocationSettingProperty
()
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
haddock_workaround_ :: ()
codeHook :: Maybe DialogCodeHookInvocationSettingProperty
confirmationConditional :: Maybe ConditionalSpecificationProperty
confirmationNextStep :: Maybe DialogStateProperty
confirmationResponse :: Maybe ResponseSpecificationProperty
declinationConditional :: Maybe ConditionalSpecificationProperty
declinationNextStep :: Maybe DialogStateProperty
declinationResponse :: Maybe ResponseSpecificationProperty
elicitationCodeHook :: Maybe ElicitationCodeHookInvocationSettingProperty
failureConditional :: Maybe ConditionalSpecificationProperty
failureNextStep :: Maybe DialogStateProperty
failureResponse :: Maybe ResponseSpecificationProperty
isActive :: Maybe (Value Bool)
..}