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