module Stratosphere.Lex.Bot.SampleUtteranceProperty (
SampleUtteranceProperty(..), mkSampleUtteranceProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SampleUtteranceProperty
=
SampleUtteranceProperty {SampleUtteranceProperty -> ()
haddock_workaround_ :: (),
SampleUtteranceProperty -> Value Text
utterance :: (Value Prelude.Text)}
deriving stock (SampleUtteranceProperty -> SampleUtteranceProperty -> Bool
(SampleUtteranceProperty -> SampleUtteranceProperty -> Bool)
-> (SampleUtteranceProperty -> SampleUtteranceProperty -> Bool)
-> Eq SampleUtteranceProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SampleUtteranceProperty -> SampleUtteranceProperty -> Bool
== :: SampleUtteranceProperty -> SampleUtteranceProperty -> Bool
$c/= :: SampleUtteranceProperty -> SampleUtteranceProperty -> Bool
/= :: SampleUtteranceProperty -> SampleUtteranceProperty -> Bool
Prelude.Eq, Int -> SampleUtteranceProperty -> ShowS
[SampleUtteranceProperty] -> ShowS
SampleUtteranceProperty -> String
(Int -> SampleUtteranceProperty -> ShowS)
-> (SampleUtteranceProperty -> String)
-> ([SampleUtteranceProperty] -> ShowS)
-> Show SampleUtteranceProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SampleUtteranceProperty -> ShowS
showsPrec :: Int -> SampleUtteranceProperty -> ShowS
$cshow :: SampleUtteranceProperty -> String
show :: SampleUtteranceProperty -> String
$cshowList :: [SampleUtteranceProperty] -> ShowS
showList :: [SampleUtteranceProperty] -> ShowS
Prelude.Show)
mkSampleUtteranceProperty ::
Value Prelude.Text -> SampleUtteranceProperty
mkSampleUtteranceProperty :: Value Text -> SampleUtteranceProperty
mkSampleUtteranceProperty Value Text
utterance
= SampleUtteranceProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), utterance :: Value Text
utterance = Value Text
utterance}
instance ToResourceProperties SampleUtteranceProperty where
toResourceProperties :: SampleUtteranceProperty -> ResourceProperties
toResourceProperties SampleUtteranceProperty {()
Value Text
haddock_workaround_ :: SampleUtteranceProperty -> ()
utterance :: SampleUtteranceProperty -> Value Text
haddock_workaround_ :: ()
utterance :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lex::Bot.SampleUtterance",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Utterance" 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
utterance]}
instance JSON.ToJSON SampleUtteranceProperty where
toJSON :: SampleUtteranceProperty -> Value
toJSON SampleUtteranceProperty {()
Value Text
haddock_workaround_ :: SampleUtteranceProperty -> ()
utterance :: SampleUtteranceProperty -> Value Text
haddock_workaround_ :: ()
utterance :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object [Key
"Utterance" 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
utterance]
instance Property "Utterance" SampleUtteranceProperty where
type PropertyType "Utterance" SampleUtteranceProperty = Value Prelude.Text
set :: PropertyType "Utterance" SampleUtteranceProperty
-> SampleUtteranceProperty -> SampleUtteranceProperty
set PropertyType "Utterance" SampleUtteranceProperty
newValue SampleUtteranceProperty {()
Value Text
haddock_workaround_ :: SampleUtteranceProperty -> ()
utterance :: SampleUtteranceProperty -> Value Text
haddock_workaround_ :: ()
utterance :: Value Text
..}
= SampleUtteranceProperty {utterance :: Value Text
utterance = PropertyType "Utterance" SampleUtteranceProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}