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