module Stratosphere.SageMaker.InferenceComponent.AutoRollbackConfigurationProperty (
module Exports, AutoRollbackConfigurationProperty(..),
mkAutoRollbackConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SageMaker.InferenceComponent.AlarmProperty as Exports
import Stratosphere.ResourceProperties
data AutoRollbackConfigurationProperty
=
AutoRollbackConfigurationProperty {AutoRollbackConfigurationProperty -> ()
haddock_workaround_ :: (),
AutoRollbackConfigurationProperty -> [AlarmProperty]
alarms :: [AlarmProperty]}
deriving stock (AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty -> Bool
(AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty -> Bool)
-> (AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty -> Bool)
-> Eq AutoRollbackConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty -> Bool
== :: AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty -> Bool
$c/= :: AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty -> Bool
/= :: AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty -> Bool
Prelude.Eq, Int -> AutoRollbackConfigurationProperty -> ShowS
[AutoRollbackConfigurationProperty] -> ShowS
AutoRollbackConfigurationProperty -> String
(Int -> AutoRollbackConfigurationProperty -> ShowS)
-> (AutoRollbackConfigurationProperty -> String)
-> ([AutoRollbackConfigurationProperty] -> ShowS)
-> Show AutoRollbackConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AutoRollbackConfigurationProperty -> ShowS
showsPrec :: Int -> AutoRollbackConfigurationProperty -> ShowS
$cshow :: AutoRollbackConfigurationProperty -> String
show :: AutoRollbackConfigurationProperty -> String
$cshowList :: [AutoRollbackConfigurationProperty] -> ShowS
showList :: [AutoRollbackConfigurationProperty] -> ShowS
Prelude.Show)
mkAutoRollbackConfigurationProperty ::
[AlarmProperty] -> AutoRollbackConfigurationProperty
mkAutoRollbackConfigurationProperty :: [AlarmProperty] -> AutoRollbackConfigurationProperty
mkAutoRollbackConfigurationProperty [AlarmProperty]
alarms
= AutoRollbackConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), alarms :: [AlarmProperty]
alarms = [AlarmProperty]
alarms}
instance ToResourceProperties AutoRollbackConfigurationProperty where
toResourceProperties :: AutoRollbackConfigurationProperty -> ResourceProperties
toResourceProperties AutoRollbackConfigurationProperty {[AlarmProperty]
()
haddock_workaround_ :: AutoRollbackConfigurationProperty -> ()
alarms :: AutoRollbackConfigurationProperty -> [AlarmProperty]
haddock_workaround_ :: ()
alarms :: [AlarmProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SageMaker::InferenceComponent.AutoRollbackConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Alarms" Key -> [AlarmProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [AlarmProperty]
alarms]}
instance JSON.ToJSON AutoRollbackConfigurationProperty where
toJSON :: AutoRollbackConfigurationProperty -> Value
toJSON AutoRollbackConfigurationProperty {[AlarmProperty]
()
haddock_workaround_ :: AutoRollbackConfigurationProperty -> ()
alarms :: AutoRollbackConfigurationProperty -> [AlarmProperty]
haddock_workaround_ :: ()
alarms :: [AlarmProperty]
..}
= [(Key, Value)] -> Value
JSON.object [Key
"Alarms" Key -> [AlarmProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [AlarmProperty]
alarms]
instance Property "Alarms" AutoRollbackConfigurationProperty where
type PropertyType "Alarms" AutoRollbackConfigurationProperty = [AlarmProperty]
set :: PropertyType "Alarms" AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty
-> AutoRollbackConfigurationProperty
set PropertyType "Alarms" AutoRollbackConfigurationProperty
newValue AutoRollbackConfigurationProperty {[AlarmProperty]
()
haddock_workaround_ :: AutoRollbackConfigurationProperty -> ()
alarms :: AutoRollbackConfigurationProperty -> [AlarmProperty]
haddock_workaround_ :: ()
alarms :: [AlarmProperty]
..}
= AutoRollbackConfigurationProperty {alarms :: [AlarmProperty]
alarms = [AlarmProperty]
PropertyType "Alarms" AutoRollbackConfigurationProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}