module Stratosphere.Lex.Bot.SlotDefaultValueProperty (
SlotDefaultValueProperty(..), mkSlotDefaultValueProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SlotDefaultValueProperty
=
SlotDefaultValueProperty {SlotDefaultValueProperty -> ()
haddock_workaround_ :: (),
SlotDefaultValueProperty -> Value Text
defaultValue :: (Value Prelude.Text)}
deriving stock (SlotDefaultValueProperty -> SlotDefaultValueProperty -> Bool
(SlotDefaultValueProperty -> SlotDefaultValueProperty -> Bool)
-> (SlotDefaultValueProperty -> SlotDefaultValueProperty -> Bool)
-> Eq SlotDefaultValueProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SlotDefaultValueProperty -> SlotDefaultValueProperty -> Bool
== :: SlotDefaultValueProperty -> SlotDefaultValueProperty -> Bool
$c/= :: SlotDefaultValueProperty -> SlotDefaultValueProperty -> Bool
/= :: SlotDefaultValueProperty -> SlotDefaultValueProperty -> Bool
Prelude.Eq, Int -> SlotDefaultValueProperty -> ShowS
[SlotDefaultValueProperty] -> ShowS
SlotDefaultValueProperty -> String
(Int -> SlotDefaultValueProperty -> ShowS)
-> (SlotDefaultValueProperty -> String)
-> ([SlotDefaultValueProperty] -> ShowS)
-> Show SlotDefaultValueProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SlotDefaultValueProperty -> ShowS
showsPrec :: Int -> SlotDefaultValueProperty -> ShowS
$cshow :: SlotDefaultValueProperty -> String
show :: SlotDefaultValueProperty -> String
$cshowList :: [SlotDefaultValueProperty] -> ShowS
showList :: [SlotDefaultValueProperty] -> ShowS
Prelude.Show)
mkSlotDefaultValueProperty ::
Value Prelude.Text -> SlotDefaultValueProperty
mkSlotDefaultValueProperty :: Value Text -> SlotDefaultValueProperty
mkSlotDefaultValueProperty Value Text
defaultValue
= SlotDefaultValueProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), defaultValue :: Value Text
defaultValue = Value Text
defaultValue}
instance ToResourceProperties SlotDefaultValueProperty where
toResourceProperties :: SlotDefaultValueProperty -> ResourceProperties
toResourceProperties SlotDefaultValueProperty {()
Value Text
haddock_workaround_ :: SlotDefaultValueProperty -> ()
defaultValue :: SlotDefaultValueProperty -> Value Text
haddock_workaround_ :: ()
defaultValue :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lex::Bot.SlotDefaultValue",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"DefaultValue" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
defaultValue]}
instance JSON.ToJSON SlotDefaultValueProperty where
toJSON :: SlotDefaultValueProperty -> Value
toJSON SlotDefaultValueProperty {()
Value Text
haddock_workaround_ :: SlotDefaultValueProperty -> ()
defaultValue :: SlotDefaultValueProperty -> Value Text
haddock_workaround_ :: ()
defaultValue :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object [Key
"DefaultValue" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
defaultValue]
instance Property "DefaultValue" SlotDefaultValueProperty where
type PropertyType "DefaultValue" SlotDefaultValueProperty = Value Prelude.Text
set :: PropertyType "DefaultValue" SlotDefaultValueProperty
-> SlotDefaultValueProperty -> SlotDefaultValueProperty
set PropertyType "DefaultValue" SlotDefaultValueProperty
newValue SlotDefaultValueProperty {()
Value Text
haddock_workaround_ :: SlotDefaultValueProperty -> ()
defaultValue :: SlotDefaultValueProperty -> Value Text
haddock_workaround_ :: ()
defaultValue :: Value Text
..}
= SlotDefaultValueProperty {defaultValue :: Value Text
defaultValue = PropertyType "DefaultValue" SlotDefaultValueProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}