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