module Stratosphere.Connect.HoursOfOperation.HoursOfOperationConfigProperty (
        module Exports, HoursOfOperationConfigProperty(..),
        mkHoursOfOperationConfigProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Connect.HoursOfOperation.HoursOfOperationTimeSliceProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data HoursOfOperationConfigProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-connect-hoursofoperation-hoursofoperationconfig.html>
    HoursOfOperationConfigProperty {HoursOfOperationConfigProperty -> ()
haddock_workaround_ :: (),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-connect-hoursofoperation-hoursofoperationconfig.html#cfn-connect-hoursofoperation-hoursofoperationconfig-day>
                                    HoursOfOperationConfigProperty -> Value Text
day :: (Value Prelude.Text),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-connect-hoursofoperation-hoursofoperationconfig.html#cfn-connect-hoursofoperation-hoursofoperationconfig-endtime>
                                    HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
endTime :: HoursOfOperationTimeSliceProperty,
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-connect-hoursofoperation-hoursofoperationconfig.html#cfn-connect-hoursofoperation-hoursofoperationconfig-starttime>
                                    HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty}
  deriving stock (HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> Bool
(HoursOfOperationConfigProperty
 -> HoursOfOperationConfigProperty -> Bool)
-> (HoursOfOperationConfigProperty
    -> HoursOfOperationConfigProperty -> Bool)
-> Eq HoursOfOperationConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> Bool
== :: HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> Bool
$c/= :: HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> Bool
/= :: HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> Bool
Prelude.Eq, Int -> HoursOfOperationConfigProperty -> ShowS
[HoursOfOperationConfigProperty] -> ShowS
HoursOfOperationConfigProperty -> String
(Int -> HoursOfOperationConfigProperty -> ShowS)
-> (HoursOfOperationConfigProperty -> String)
-> ([HoursOfOperationConfigProperty] -> ShowS)
-> Show HoursOfOperationConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HoursOfOperationConfigProperty -> ShowS
showsPrec :: Int -> HoursOfOperationConfigProperty -> ShowS
$cshow :: HoursOfOperationConfigProperty -> String
show :: HoursOfOperationConfigProperty -> String
$cshowList :: [HoursOfOperationConfigProperty] -> ShowS
showList :: [HoursOfOperationConfigProperty] -> ShowS
Prelude.Show)
mkHoursOfOperationConfigProperty ::
  Value Prelude.Text
  -> HoursOfOperationTimeSliceProperty
     -> HoursOfOperationTimeSliceProperty
        -> HoursOfOperationConfigProperty
mkHoursOfOperationConfigProperty :: Value Text
-> HoursOfOperationTimeSliceProperty
-> HoursOfOperationTimeSliceProperty
-> HoursOfOperationConfigProperty
mkHoursOfOperationConfigProperty Value Text
day HoursOfOperationTimeSliceProperty
endTime HoursOfOperationTimeSliceProperty
startTime
  = HoursOfOperationConfigProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), day :: Value Text
day = Value Text
day, endTime :: HoursOfOperationTimeSliceProperty
endTime = HoursOfOperationTimeSliceProperty
endTime,
       startTime :: HoursOfOperationTimeSliceProperty
startTime = HoursOfOperationTimeSliceProperty
startTime}
instance ToResourceProperties HoursOfOperationConfigProperty where
  toResourceProperties :: HoursOfOperationConfigProperty -> ResourceProperties
toResourceProperties HoursOfOperationConfigProperty {()
Value Text
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: HoursOfOperationConfigProperty -> ()
day :: HoursOfOperationConfigProperty -> Value Text
endTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
endTime :: HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Connect::HoursOfOperation.HoursOfOperationConfig",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Day" 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
day, Key
"EndTime" Key -> HoursOfOperationTimeSliceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= HoursOfOperationTimeSliceProperty
endTime,
                       Key
"StartTime" Key -> HoursOfOperationTimeSliceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= HoursOfOperationTimeSliceProperty
startTime]}
instance JSON.ToJSON HoursOfOperationConfigProperty where
  toJSON :: HoursOfOperationConfigProperty -> Value
toJSON HoursOfOperationConfigProperty {()
Value Text
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: HoursOfOperationConfigProperty -> ()
day :: HoursOfOperationConfigProperty -> Value Text
endTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
endTime :: HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"Day" 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
day, Key
"EndTime" Key -> HoursOfOperationTimeSliceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= HoursOfOperationTimeSliceProperty
endTime,
         Key
"StartTime" Key -> HoursOfOperationTimeSliceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= HoursOfOperationTimeSliceProperty
startTime]
instance Property "Day" HoursOfOperationConfigProperty where
  type PropertyType "Day" HoursOfOperationConfigProperty = Value Prelude.Text
  set :: PropertyType "Day" HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> HoursOfOperationConfigProperty
set PropertyType "Day" HoursOfOperationConfigProperty
newValue HoursOfOperationConfigProperty {()
Value Text
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: HoursOfOperationConfigProperty -> ()
day :: HoursOfOperationConfigProperty -> Value Text
endTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
endTime :: HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty
..}
    = HoursOfOperationConfigProperty {day :: Value Text
day = PropertyType "Day" HoursOfOperationConfigProperty
Value Text
newValue, ()
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
endTime :: HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
endTime :: HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty
..}
instance Property "EndTime" HoursOfOperationConfigProperty where
  type PropertyType "EndTime" HoursOfOperationConfigProperty = HoursOfOperationTimeSliceProperty
  set :: PropertyType "EndTime" HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> HoursOfOperationConfigProperty
set PropertyType "EndTime" HoursOfOperationConfigProperty
newValue HoursOfOperationConfigProperty {()
Value Text
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: HoursOfOperationConfigProperty -> ()
day :: HoursOfOperationConfigProperty -> Value Text
endTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
endTime :: HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty
..}
    = HoursOfOperationConfigProperty {endTime :: HoursOfOperationTimeSliceProperty
endTime = PropertyType "EndTime" HoursOfOperationConfigProperty
HoursOfOperationTimeSliceProperty
newValue, ()
Value Text
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
startTime :: HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
startTime :: HoursOfOperationTimeSliceProperty
..}
instance Property "StartTime" HoursOfOperationConfigProperty where
  type PropertyType "StartTime" HoursOfOperationConfigProperty = HoursOfOperationTimeSliceProperty
  set :: PropertyType "StartTime" HoursOfOperationConfigProperty
-> HoursOfOperationConfigProperty -> HoursOfOperationConfigProperty
set PropertyType "StartTime" HoursOfOperationConfigProperty
newValue HoursOfOperationConfigProperty {()
Value Text
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: HoursOfOperationConfigProperty -> ()
day :: HoursOfOperationConfigProperty -> Value Text
endTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationConfigProperty -> HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
endTime :: HoursOfOperationTimeSliceProperty
startTime :: HoursOfOperationTimeSliceProperty
..}
    = HoursOfOperationConfigProperty {startTime :: HoursOfOperationTimeSliceProperty
startTime = PropertyType "StartTime" HoursOfOperationConfigProperty
HoursOfOperationTimeSliceProperty
newValue, ()
Value Text
HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
endTime :: HoursOfOperationTimeSliceProperty
haddock_workaround_ :: ()
day :: Value Text
endTime :: HoursOfOperationTimeSliceProperty
..}