module Stratosphere.Lex.Bot.DialogStateProperty (
module Exports, DialogStateProperty(..), mkDialogStateProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Lex.Bot.DialogActionProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.IntentOverrideProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.SessionAttributeProperty as Exports
import Stratosphere.ResourceProperties
data DialogStateProperty
=
DialogStateProperty {DialogStateProperty -> ()
haddock_workaround_ :: (),
DialogStateProperty -> Maybe DialogActionProperty
dialogAction :: (Prelude.Maybe DialogActionProperty),
DialogStateProperty -> Maybe IntentOverrideProperty
intent :: (Prelude.Maybe IntentOverrideProperty),
DialogStateProperty -> Maybe [SessionAttributeProperty]
sessionAttributes :: (Prelude.Maybe [SessionAttributeProperty])}
deriving stock (DialogStateProperty -> DialogStateProperty -> Bool
(DialogStateProperty -> DialogStateProperty -> Bool)
-> (DialogStateProperty -> DialogStateProperty -> Bool)
-> Eq DialogStateProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DialogStateProperty -> DialogStateProperty -> Bool
== :: DialogStateProperty -> DialogStateProperty -> Bool
$c/= :: DialogStateProperty -> DialogStateProperty -> Bool
/= :: DialogStateProperty -> DialogStateProperty -> Bool
Prelude.Eq, Int -> DialogStateProperty -> ShowS
[DialogStateProperty] -> ShowS
DialogStateProperty -> String
(Int -> DialogStateProperty -> ShowS)
-> (DialogStateProperty -> String)
-> ([DialogStateProperty] -> ShowS)
-> Show DialogStateProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DialogStateProperty -> ShowS
showsPrec :: Int -> DialogStateProperty -> ShowS
$cshow :: DialogStateProperty -> String
show :: DialogStateProperty -> String
$cshowList :: [DialogStateProperty] -> ShowS
showList :: [DialogStateProperty] -> ShowS
Prelude.Show)
mkDialogStateProperty :: DialogStateProperty
mkDialogStateProperty :: DialogStateProperty
mkDialogStateProperty
= DialogStateProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), dialogAction :: Maybe DialogActionProperty
dialogAction = Maybe DialogActionProperty
forall a. Maybe a
Prelude.Nothing,
intent :: Maybe IntentOverrideProperty
intent = Maybe IntentOverrideProperty
forall a. Maybe a
Prelude.Nothing, sessionAttributes :: Maybe [SessionAttributeProperty]
sessionAttributes = Maybe [SessionAttributeProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties DialogStateProperty where
toResourceProperties :: DialogStateProperty -> ResourceProperties
toResourceProperties DialogStateProperty {Maybe [SessionAttributeProperty]
Maybe DialogActionProperty
Maybe IntentOverrideProperty
()
haddock_workaround_ :: DialogStateProperty -> ()
dialogAction :: DialogStateProperty -> Maybe DialogActionProperty
intent :: DialogStateProperty -> Maybe IntentOverrideProperty
sessionAttributes :: DialogStateProperty -> Maybe [SessionAttributeProperty]
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
intent :: Maybe IntentOverrideProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lex::Bot.DialogState",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> DialogActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DialogAction" (DialogActionProperty -> (Key, Value))
-> Maybe DialogActionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogActionProperty
dialogAction,
Key -> IntentOverrideProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Intent" (IntentOverrideProperty -> (Key, Value))
-> Maybe IntentOverrideProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IntentOverrideProperty
intent,
Key -> [SessionAttributeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SessionAttributes" ([SessionAttributeProperty] -> (Key, Value))
-> Maybe [SessionAttributeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SessionAttributeProperty]
sessionAttributes])}
instance JSON.ToJSON DialogStateProperty where
toJSON :: DialogStateProperty -> Value
toJSON DialogStateProperty {Maybe [SessionAttributeProperty]
Maybe DialogActionProperty
Maybe IntentOverrideProperty
()
haddock_workaround_ :: DialogStateProperty -> ()
dialogAction :: DialogStateProperty -> Maybe DialogActionProperty
intent :: DialogStateProperty -> Maybe IntentOverrideProperty
sessionAttributes :: DialogStateProperty -> Maybe [SessionAttributeProperty]
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
intent :: Maybe IntentOverrideProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> DialogActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DialogAction" (DialogActionProperty -> (Key, Value))
-> Maybe DialogActionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DialogActionProperty
dialogAction,
Key -> IntentOverrideProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Intent" (IntentOverrideProperty -> (Key, Value))
-> Maybe IntentOverrideProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IntentOverrideProperty
intent,
Key -> [SessionAttributeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SessionAttributes" ([SessionAttributeProperty] -> (Key, Value))
-> Maybe [SessionAttributeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SessionAttributeProperty]
sessionAttributes]))
instance Property "DialogAction" DialogStateProperty where
type PropertyType "DialogAction" DialogStateProperty = DialogActionProperty
set :: PropertyType "DialogAction" DialogStateProperty
-> DialogStateProperty -> DialogStateProperty
set PropertyType "DialogAction" DialogStateProperty
newValue DialogStateProperty {Maybe [SessionAttributeProperty]
Maybe DialogActionProperty
Maybe IntentOverrideProperty
()
haddock_workaround_ :: DialogStateProperty -> ()
dialogAction :: DialogStateProperty -> Maybe DialogActionProperty
intent :: DialogStateProperty -> Maybe IntentOverrideProperty
sessionAttributes :: DialogStateProperty -> Maybe [SessionAttributeProperty]
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
intent :: Maybe IntentOverrideProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
..}
= DialogStateProperty {dialogAction :: Maybe DialogActionProperty
dialogAction = DialogActionProperty -> Maybe DialogActionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DialogAction" DialogStateProperty
DialogActionProperty
newValue, Maybe [SessionAttributeProperty]
Maybe IntentOverrideProperty
()
haddock_workaround_ :: ()
intent :: Maybe IntentOverrideProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
haddock_workaround_ :: ()
intent :: Maybe IntentOverrideProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
..}
instance Property "Intent" DialogStateProperty where
type PropertyType "Intent" DialogStateProperty = IntentOverrideProperty
set :: PropertyType "Intent" DialogStateProperty
-> DialogStateProperty -> DialogStateProperty
set PropertyType "Intent" DialogStateProperty
newValue DialogStateProperty {Maybe [SessionAttributeProperty]
Maybe DialogActionProperty
Maybe IntentOverrideProperty
()
haddock_workaround_ :: DialogStateProperty -> ()
dialogAction :: DialogStateProperty -> Maybe DialogActionProperty
intent :: DialogStateProperty -> Maybe IntentOverrideProperty
sessionAttributes :: DialogStateProperty -> Maybe [SessionAttributeProperty]
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
intent :: Maybe IntentOverrideProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
..}
= DialogStateProperty {intent :: Maybe IntentOverrideProperty
intent = IntentOverrideProperty -> Maybe IntentOverrideProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Intent" DialogStateProperty
IntentOverrideProperty
newValue, Maybe [SessionAttributeProperty]
Maybe DialogActionProperty
()
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
..}
instance Property "SessionAttributes" DialogStateProperty where
type PropertyType "SessionAttributes" DialogStateProperty = [SessionAttributeProperty]
set :: PropertyType "SessionAttributes" DialogStateProperty
-> DialogStateProperty -> DialogStateProperty
set PropertyType "SessionAttributes" DialogStateProperty
newValue DialogStateProperty {Maybe [SessionAttributeProperty]
Maybe DialogActionProperty
Maybe IntentOverrideProperty
()
haddock_workaround_ :: DialogStateProperty -> ()
dialogAction :: DialogStateProperty -> Maybe DialogActionProperty
intent :: DialogStateProperty -> Maybe IntentOverrideProperty
sessionAttributes :: DialogStateProperty -> Maybe [SessionAttributeProperty]
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
intent :: Maybe IntentOverrideProperty
sessionAttributes :: Maybe [SessionAttributeProperty]
..}
= DialogStateProperty
{sessionAttributes :: Maybe [SessionAttributeProperty]
sessionAttributes = [SessionAttributeProperty] -> Maybe [SessionAttributeProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SessionAttributeProperty]
PropertyType "SessionAttributes" DialogStateProperty
newValue, Maybe DialogActionProperty
Maybe IntentOverrideProperty
()
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
intent :: Maybe IntentOverrideProperty
haddock_workaround_ :: ()
dialogAction :: Maybe DialogActionProperty
intent :: Maybe IntentOverrideProperty
..}