module Stratosphere.InspectorV2.CisScanConfiguration.WeeklyScheduleProperty (
        module Exports, WeeklyScheduleProperty(..),
        mkWeeklyScheduleProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.InspectorV2.CisScanConfiguration.TimeProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data WeeklyScheduleProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-inspectorv2-cisscanconfiguration-weeklyschedule.html>
    WeeklyScheduleProperty {WeeklyScheduleProperty -> ()
haddock_workaround_ :: (),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-inspectorv2-cisscanconfiguration-weeklyschedule.html#cfn-inspectorv2-cisscanconfiguration-weeklyschedule-days>
                            WeeklyScheduleProperty -> ValueList Text
days :: (ValueList Prelude.Text),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-inspectorv2-cisscanconfiguration-weeklyschedule.html#cfn-inspectorv2-cisscanconfiguration-weeklyschedule-starttime>
                            WeeklyScheduleProperty -> TimeProperty
startTime :: TimeProperty}
  deriving stock (WeeklyScheduleProperty -> WeeklyScheduleProperty -> Bool
(WeeklyScheduleProperty -> WeeklyScheduleProperty -> Bool)
-> (WeeklyScheduleProperty -> WeeklyScheduleProperty -> Bool)
-> Eq WeeklyScheduleProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WeeklyScheduleProperty -> WeeklyScheduleProperty -> Bool
== :: WeeklyScheduleProperty -> WeeklyScheduleProperty -> Bool
$c/= :: WeeklyScheduleProperty -> WeeklyScheduleProperty -> Bool
/= :: WeeklyScheduleProperty -> WeeklyScheduleProperty -> Bool
Prelude.Eq, Int -> WeeklyScheduleProperty -> ShowS
[WeeklyScheduleProperty] -> ShowS
WeeklyScheduleProperty -> String
(Int -> WeeklyScheduleProperty -> ShowS)
-> (WeeklyScheduleProperty -> String)
-> ([WeeklyScheduleProperty] -> ShowS)
-> Show WeeklyScheduleProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WeeklyScheduleProperty -> ShowS
showsPrec :: Int -> WeeklyScheduleProperty -> ShowS
$cshow :: WeeklyScheduleProperty -> String
show :: WeeklyScheduleProperty -> String
$cshowList :: [WeeklyScheduleProperty] -> ShowS
showList :: [WeeklyScheduleProperty] -> ShowS
Prelude.Show)
mkWeeklyScheduleProperty ::
  ValueList Prelude.Text -> TimeProperty -> WeeklyScheduleProperty
mkWeeklyScheduleProperty :: ValueList Text -> TimeProperty -> WeeklyScheduleProperty
mkWeeklyScheduleProperty ValueList Text
days TimeProperty
startTime
  = WeeklyScheduleProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), days :: ValueList Text
days = ValueList Text
days, startTime :: TimeProperty
startTime = TimeProperty
startTime}
instance ToResourceProperties WeeklyScheduleProperty where
  toResourceProperties :: WeeklyScheduleProperty -> ResourceProperties
toResourceProperties WeeklyScheduleProperty {()
ValueList Text
TimeProperty
haddock_workaround_ :: WeeklyScheduleProperty -> ()
days :: WeeklyScheduleProperty -> ValueList Text
startTime :: WeeklyScheduleProperty -> TimeProperty
haddock_workaround_ :: ()
days :: ValueList Text
startTime :: TimeProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::InspectorV2::CisScanConfiguration.WeeklySchedule",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Days" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
days, Key
"StartTime" Key -> TimeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= TimeProperty
startTime]}
instance JSON.ToJSON WeeklyScheduleProperty where
  toJSON :: WeeklyScheduleProperty -> Value
toJSON WeeklyScheduleProperty {()
ValueList Text
TimeProperty
haddock_workaround_ :: WeeklyScheduleProperty -> ()
days :: WeeklyScheduleProperty -> ValueList Text
startTime :: WeeklyScheduleProperty -> TimeProperty
haddock_workaround_ :: ()
days :: ValueList Text
startTime :: TimeProperty
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Days" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
days, Key
"StartTime" Key -> TimeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= TimeProperty
startTime]
instance Property "Days" WeeklyScheduleProperty where
  type PropertyType "Days" WeeklyScheduleProperty = ValueList Prelude.Text
  set :: PropertyType "Days" WeeklyScheduleProperty
-> WeeklyScheduleProperty -> WeeklyScheduleProperty
set PropertyType "Days" WeeklyScheduleProperty
newValue WeeklyScheduleProperty {()
ValueList Text
TimeProperty
haddock_workaround_ :: WeeklyScheduleProperty -> ()
days :: WeeklyScheduleProperty -> ValueList Text
startTime :: WeeklyScheduleProperty -> TimeProperty
haddock_workaround_ :: ()
days :: ValueList Text
startTime :: TimeProperty
..}
    = WeeklyScheduleProperty {days :: ValueList Text
days = PropertyType "Days" WeeklyScheduleProperty
ValueList Text
newValue, ()
TimeProperty
haddock_workaround_ :: ()
startTime :: TimeProperty
haddock_workaround_ :: ()
startTime :: TimeProperty
..}
instance Property "StartTime" WeeklyScheduleProperty where
  type PropertyType "StartTime" WeeklyScheduleProperty = TimeProperty
  set :: PropertyType "StartTime" WeeklyScheduleProperty
-> WeeklyScheduleProperty -> WeeklyScheduleProperty
set PropertyType "StartTime" WeeklyScheduleProperty
newValue WeeklyScheduleProperty {()
ValueList Text
TimeProperty
haddock_workaround_ :: WeeklyScheduleProperty -> ()
days :: WeeklyScheduleProperty -> ValueList Text
startTime :: WeeklyScheduleProperty -> TimeProperty
haddock_workaround_ :: ()
days :: ValueList Text
startTime :: TimeProperty
..}
    = WeeklyScheduleProperty {startTime :: TimeProperty
startTime = PropertyType "StartTime" WeeklyScheduleProperty
TimeProperty
newValue, ()
ValueList Text
haddock_workaround_ :: ()
days :: ValueList Text
haddock_workaround_ :: ()
days :: ValueList Text
..}