module Stratosphere.ApplicationSignals.ServiceLevelObjective.ExclusionWindowProperty (
module Exports, ExclusionWindowProperty(..),
mkExclusionWindowProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.ApplicationSignals.ServiceLevelObjective.RecurrenceRuleProperty as Exports
import {-# SOURCE #-} Stratosphere.ApplicationSignals.ServiceLevelObjective.WindowProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ExclusionWindowProperty
=
ExclusionWindowProperty {ExclusionWindowProperty -> ()
haddock_workaround_ :: (),
ExclusionWindowProperty -> Maybe (Value Text)
reason :: (Prelude.Maybe (Value Prelude.Text)),
ExclusionWindowProperty -> Maybe RecurrenceRuleProperty
recurrenceRule :: (Prelude.Maybe RecurrenceRuleProperty),
ExclusionWindowProperty -> Maybe (Value Text)
startTime :: (Prelude.Maybe (Value Prelude.Text)),
ExclusionWindowProperty -> WindowProperty
window :: WindowProperty}
deriving stock (ExclusionWindowProperty -> ExclusionWindowProperty -> Bool
(ExclusionWindowProperty -> ExclusionWindowProperty -> Bool)
-> (ExclusionWindowProperty -> ExclusionWindowProperty -> Bool)
-> Eq ExclusionWindowProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExclusionWindowProperty -> ExclusionWindowProperty -> Bool
== :: ExclusionWindowProperty -> ExclusionWindowProperty -> Bool
$c/= :: ExclusionWindowProperty -> ExclusionWindowProperty -> Bool
/= :: ExclusionWindowProperty -> ExclusionWindowProperty -> Bool
Prelude.Eq, Int -> ExclusionWindowProperty -> ShowS
[ExclusionWindowProperty] -> ShowS
ExclusionWindowProperty -> String
(Int -> ExclusionWindowProperty -> ShowS)
-> (ExclusionWindowProperty -> String)
-> ([ExclusionWindowProperty] -> ShowS)
-> Show ExclusionWindowProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExclusionWindowProperty -> ShowS
showsPrec :: Int -> ExclusionWindowProperty -> ShowS
$cshow :: ExclusionWindowProperty -> String
show :: ExclusionWindowProperty -> String
$cshowList :: [ExclusionWindowProperty] -> ShowS
showList :: [ExclusionWindowProperty] -> ShowS
Prelude.Show)
mkExclusionWindowProperty ::
WindowProperty -> ExclusionWindowProperty
mkExclusionWindowProperty :: WindowProperty -> ExclusionWindowProperty
mkExclusionWindowProperty WindowProperty
window
= ExclusionWindowProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), window :: WindowProperty
window = WindowProperty
window,
reason :: Maybe (Value Text)
reason = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, recurrenceRule :: Maybe RecurrenceRuleProperty
recurrenceRule = Maybe RecurrenceRuleProperty
forall a. Maybe a
Prelude.Nothing,
startTime :: Maybe (Value Text)
startTime = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ExclusionWindowProperty where
toResourceProperties :: ExclusionWindowProperty -> ResourceProperties
toResourceProperties ExclusionWindowProperty {Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ExclusionWindowProperty -> ()
reason :: ExclusionWindowProperty -> Maybe (Value Text)
recurrenceRule :: ExclusionWindowProperty -> Maybe RecurrenceRuleProperty
startTime :: ExclusionWindowProperty -> Maybe (Value Text)
window :: ExclusionWindowProperty -> WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::ApplicationSignals::ServiceLevelObjective.ExclusionWindow",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Window" Key -> WindowProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= WindowProperty
window]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"Reason" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
reason,
Key -> RecurrenceRuleProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RecurrenceRule" (RecurrenceRuleProperty -> (Key, Value))
-> Maybe RecurrenceRuleProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RecurrenceRuleProperty
recurrenceRule,
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..=) Key
"StartTime" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
startTime]))}
instance JSON.ToJSON ExclusionWindowProperty where
toJSON :: ExclusionWindowProperty -> Value
toJSON ExclusionWindowProperty {Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ExclusionWindowProperty -> ()
reason :: ExclusionWindowProperty -> Maybe (Value Text)
recurrenceRule :: ExclusionWindowProperty -> Maybe RecurrenceRuleProperty
startTime :: ExclusionWindowProperty -> Maybe (Value Text)
window :: ExclusionWindowProperty -> WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Window" Key -> WindowProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= WindowProperty
window]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"Reason" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
reason,
Key -> RecurrenceRuleProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RecurrenceRule" (RecurrenceRuleProperty -> (Key, Value))
-> Maybe RecurrenceRuleProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RecurrenceRuleProperty
recurrenceRule,
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..=) Key
"StartTime" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
startTime])))
instance Property "Reason" ExclusionWindowProperty where
type PropertyType "Reason" ExclusionWindowProperty = Value Prelude.Text
set :: PropertyType "Reason" ExclusionWindowProperty
-> ExclusionWindowProperty -> ExclusionWindowProperty
set PropertyType "Reason" ExclusionWindowProperty
newValue ExclusionWindowProperty {Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ExclusionWindowProperty -> ()
reason :: ExclusionWindowProperty -> Maybe (Value Text)
recurrenceRule :: ExclusionWindowProperty -> Maybe RecurrenceRuleProperty
startTime :: ExclusionWindowProperty -> Maybe (Value Text)
window :: ExclusionWindowProperty -> WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
= ExclusionWindowProperty {reason :: Maybe (Value Text)
reason = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Reason" ExclusionWindowProperty
Value Text
newValue, Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ()
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
haddock_workaround_ :: ()
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
instance Property "RecurrenceRule" ExclusionWindowProperty where
type PropertyType "RecurrenceRule" ExclusionWindowProperty = RecurrenceRuleProperty
set :: PropertyType "RecurrenceRule" ExclusionWindowProperty
-> ExclusionWindowProperty -> ExclusionWindowProperty
set PropertyType "RecurrenceRule" ExclusionWindowProperty
newValue ExclusionWindowProperty {Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ExclusionWindowProperty -> ()
reason :: ExclusionWindowProperty -> Maybe (Value Text)
recurrenceRule :: ExclusionWindowProperty -> Maybe RecurrenceRuleProperty
startTime :: ExclusionWindowProperty -> Maybe (Value Text)
window :: ExclusionWindowProperty -> WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
= ExclusionWindowProperty
{recurrenceRule :: Maybe RecurrenceRuleProperty
recurrenceRule = RecurrenceRuleProperty -> Maybe RecurrenceRuleProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RecurrenceRule" ExclusionWindowProperty
RecurrenceRuleProperty
newValue, Maybe (Value Text)
()
WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
startTime :: Maybe (Value Text)
window :: WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
instance Property "StartTime" ExclusionWindowProperty where
type PropertyType "StartTime" ExclusionWindowProperty = Value Prelude.Text
set :: PropertyType "StartTime" ExclusionWindowProperty
-> ExclusionWindowProperty -> ExclusionWindowProperty
set PropertyType "StartTime" ExclusionWindowProperty
newValue ExclusionWindowProperty {Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ExclusionWindowProperty -> ()
reason :: ExclusionWindowProperty -> Maybe (Value Text)
recurrenceRule :: ExclusionWindowProperty -> Maybe RecurrenceRuleProperty
startTime :: ExclusionWindowProperty -> Maybe (Value Text)
window :: ExclusionWindowProperty -> WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
= ExclusionWindowProperty {startTime :: Maybe (Value Text)
startTime = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "StartTime" ExclusionWindowProperty
Value Text
newValue, Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
window :: WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
window :: WindowProperty
..}
instance Property "Window" ExclusionWindowProperty where
type PropertyType "Window" ExclusionWindowProperty = WindowProperty
set :: PropertyType "Window" ExclusionWindowProperty
-> ExclusionWindowProperty -> ExclusionWindowProperty
set PropertyType "Window" ExclusionWindowProperty
newValue ExclusionWindowProperty {Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
WindowProperty
haddock_workaround_ :: ExclusionWindowProperty -> ()
reason :: ExclusionWindowProperty -> Maybe (Value Text)
recurrenceRule :: ExclusionWindowProperty -> Maybe RecurrenceRuleProperty
startTime :: ExclusionWindowProperty -> Maybe (Value Text)
window :: ExclusionWindowProperty -> WindowProperty
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
window :: WindowProperty
..}
= ExclusionWindowProperty {window :: WindowProperty
window = PropertyType "Window" ExclusionWindowProperty
WindowProperty
newValue, Maybe (Value Text)
Maybe RecurrenceRuleProperty
()
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
haddock_workaround_ :: ()
reason :: Maybe (Value Text)
recurrenceRule :: Maybe RecurrenceRuleProperty
startTime :: Maybe (Value Text)
..}