{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.BackupGateway.Types.MaintenanceStartTime
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.BackupGateway.Types.MaintenanceStartTime where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | This is your gateway\'s weekly maintenance start time including the day
-- and time of the week. Note that values are in terms of the gateway\'s
-- time zone. Can be weekly or monthly.
--
-- /See:/ 'newMaintenanceStartTime' smart constructor.
data MaintenanceStartTime = MaintenanceStartTime'
  { -- | The day of the month component of the maintenance start time represented
    -- as an ordinal number from 1 to 28, where 1 represents the first day of
    -- the month and 28 represents the last day of the month.
    MaintenanceStartTime -> Maybe Natural
dayOfMonth :: Prelude.Maybe Prelude.Natural,
    -- | An ordinal number between 0 and 6 that represents the day of the week,
    -- where 0 represents Sunday and 6 represents Saturday. The day of week is
    -- in the time zone of the gateway.
    MaintenanceStartTime -> Maybe Natural
dayOfWeek :: Prelude.Maybe Prelude.Natural,
    -- | The hour component of the maintenance start time represented as /hh/,
    -- where /hh/ is the hour (0 to 23). The hour of the day is in the time
    -- zone of the gateway.
    MaintenanceStartTime -> Natural
hourOfDay :: Prelude.Natural,
    -- | The minute component of the maintenance start time represented as /mm/,
    -- where /mm/ is the minute (0 to 59). The minute of the hour is in the
    -- time zone of the gateway.
    MaintenanceStartTime -> Natural
minuteOfHour :: Prelude.Natural
  }
  deriving (MaintenanceStartTime -> MaintenanceStartTime -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaintenanceStartTime -> MaintenanceStartTime -> Bool
$c/= :: MaintenanceStartTime -> MaintenanceStartTime -> Bool
== :: MaintenanceStartTime -> MaintenanceStartTime -> Bool
$c== :: MaintenanceStartTime -> MaintenanceStartTime -> Bool
Prelude.Eq, ReadPrec [MaintenanceStartTime]
ReadPrec MaintenanceStartTime
Int -> ReadS MaintenanceStartTime
ReadS [MaintenanceStartTime]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MaintenanceStartTime]
$creadListPrec :: ReadPrec [MaintenanceStartTime]
readPrec :: ReadPrec MaintenanceStartTime
$creadPrec :: ReadPrec MaintenanceStartTime
readList :: ReadS [MaintenanceStartTime]
$creadList :: ReadS [MaintenanceStartTime]
readsPrec :: Int -> ReadS MaintenanceStartTime
$creadsPrec :: Int -> ReadS MaintenanceStartTime
Prelude.Read, Int -> MaintenanceStartTime -> ShowS
[MaintenanceStartTime] -> ShowS
MaintenanceStartTime -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaintenanceStartTime] -> ShowS
$cshowList :: [MaintenanceStartTime] -> ShowS
show :: MaintenanceStartTime -> String
$cshow :: MaintenanceStartTime -> String
showsPrec :: Int -> MaintenanceStartTime -> ShowS
$cshowsPrec :: Int -> MaintenanceStartTime -> ShowS
Prelude.Show, forall x. Rep MaintenanceStartTime x -> MaintenanceStartTime
forall x. MaintenanceStartTime -> Rep MaintenanceStartTime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MaintenanceStartTime x -> MaintenanceStartTime
$cfrom :: forall x. MaintenanceStartTime -> Rep MaintenanceStartTime x
Prelude.Generic)

-- |
-- Create a value of 'MaintenanceStartTime' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'dayOfMonth', 'maintenanceStartTime_dayOfMonth' - The day of the month component of the maintenance start time represented
-- as an ordinal number from 1 to 28, where 1 represents the first day of
-- the month and 28 represents the last day of the month.
--
-- 'dayOfWeek', 'maintenanceStartTime_dayOfWeek' - An ordinal number between 0 and 6 that represents the day of the week,
-- where 0 represents Sunday and 6 represents Saturday. The day of week is
-- in the time zone of the gateway.
--
-- 'hourOfDay', 'maintenanceStartTime_hourOfDay' - The hour component of the maintenance start time represented as /hh/,
-- where /hh/ is the hour (0 to 23). The hour of the day is in the time
-- zone of the gateway.
--
-- 'minuteOfHour', 'maintenanceStartTime_minuteOfHour' - The minute component of the maintenance start time represented as /mm/,
-- where /mm/ is the minute (0 to 59). The minute of the hour is in the
-- time zone of the gateway.
newMaintenanceStartTime ::
  -- | 'hourOfDay'
  Prelude.Natural ->
  -- | 'minuteOfHour'
  Prelude.Natural ->
  MaintenanceStartTime
newMaintenanceStartTime :: Natural -> Natural -> MaintenanceStartTime
newMaintenanceStartTime Natural
pHourOfDay_ Natural
pMinuteOfHour_ =
  MaintenanceStartTime'
    { $sel:dayOfMonth:MaintenanceStartTime' :: Maybe Natural
dayOfMonth = forall a. Maybe a
Prelude.Nothing,
      $sel:dayOfWeek:MaintenanceStartTime' :: Maybe Natural
dayOfWeek = forall a. Maybe a
Prelude.Nothing,
      $sel:hourOfDay:MaintenanceStartTime' :: Natural
hourOfDay = Natural
pHourOfDay_,
      $sel:minuteOfHour:MaintenanceStartTime' :: Natural
minuteOfHour = Natural
pMinuteOfHour_
    }

-- | The day of the month component of the maintenance start time represented
-- as an ordinal number from 1 to 28, where 1 represents the first day of
-- the month and 28 represents the last day of the month.
maintenanceStartTime_dayOfMonth :: Lens.Lens' MaintenanceStartTime (Prelude.Maybe Prelude.Natural)
maintenanceStartTime_dayOfMonth :: Lens' MaintenanceStartTime (Maybe Natural)
maintenanceStartTime_dayOfMonth = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceStartTime' {Maybe Natural
dayOfMonth :: Maybe Natural
$sel:dayOfMonth:MaintenanceStartTime' :: MaintenanceStartTime -> Maybe Natural
dayOfMonth} -> Maybe Natural
dayOfMonth) (\s :: MaintenanceStartTime
s@MaintenanceStartTime' {} Maybe Natural
a -> MaintenanceStartTime
s {$sel:dayOfMonth:MaintenanceStartTime' :: Maybe Natural
dayOfMonth = Maybe Natural
a} :: MaintenanceStartTime)

-- | An ordinal number between 0 and 6 that represents the day of the week,
-- where 0 represents Sunday and 6 represents Saturday. The day of week is
-- in the time zone of the gateway.
maintenanceStartTime_dayOfWeek :: Lens.Lens' MaintenanceStartTime (Prelude.Maybe Prelude.Natural)
maintenanceStartTime_dayOfWeek :: Lens' MaintenanceStartTime (Maybe Natural)
maintenanceStartTime_dayOfWeek = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceStartTime' {Maybe Natural
dayOfWeek :: Maybe Natural
$sel:dayOfWeek:MaintenanceStartTime' :: MaintenanceStartTime -> Maybe Natural
dayOfWeek} -> Maybe Natural
dayOfWeek) (\s :: MaintenanceStartTime
s@MaintenanceStartTime' {} Maybe Natural
a -> MaintenanceStartTime
s {$sel:dayOfWeek:MaintenanceStartTime' :: Maybe Natural
dayOfWeek = Maybe Natural
a} :: MaintenanceStartTime)

-- | The hour component of the maintenance start time represented as /hh/,
-- where /hh/ is the hour (0 to 23). The hour of the day is in the time
-- zone of the gateway.
maintenanceStartTime_hourOfDay :: Lens.Lens' MaintenanceStartTime Prelude.Natural
maintenanceStartTime_hourOfDay :: Lens' MaintenanceStartTime Natural
maintenanceStartTime_hourOfDay = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceStartTime' {Natural
hourOfDay :: Natural
$sel:hourOfDay:MaintenanceStartTime' :: MaintenanceStartTime -> Natural
hourOfDay} -> Natural
hourOfDay) (\s :: MaintenanceStartTime
s@MaintenanceStartTime' {} Natural
a -> MaintenanceStartTime
s {$sel:hourOfDay:MaintenanceStartTime' :: Natural
hourOfDay = Natural
a} :: MaintenanceStartTime)

-- | The minute component of the maintenance start time represented as /mm/,
-- where /mm/ is the minute (0 to 59). The minute of the hour is in the
-- time zone of the gateway.
maintenanceStartTime_minuteOfHour :: Lens.Lens' MaintenanceStartTime Prelude.Natural
maintenanceStartTime_minuteOfHour :: Lens' MaintenanceStartTime Natural
maintenanceStartTime_minuteOfHour = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceStartTime' {Natural
minuteOfHour :: Natural
$sel:minuteOfHour:MaintenanceStartTime' :: MaintenanceStartTime -> Natural
minuteOfHour} -> Natural
minuteOfHour) (\s :: MaintenanceStartTime
s@MaintenanceStartTime' {} Natural
a -> MaintenanceStartTime
s {$sel:minuteOfHour:MaintenanceStartTime' :: Natural
minuteOfHour = Natural
a} :: MaintenanceStartTime)

instance Data.FromJSON MaintenanceStartTime where
  parseJSON :: Value -> Parser MaintenanceStartTime
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MaintenanceStartTime"
      ( \Object
x ->
          Maybe Natural
-> Maybe Natural -> Natural -> Natural -> MaintenanceStartTime
MaintenanceStartTime'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DayOfMonth")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DayOfWeek")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"HourOfDay")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"MinuteOfHour")
      )

instance Prelude.Hashable MaintenanceStartTime where
  hashWithSalt :: Int -> MaintenanceStartTime -> Int
hashWithSalt Int
_salt MaintenanceStartTime' {Natural
Maybe Natural
minuteOfHour :: Natural
hourOfDay :: Natural
dayOfWeek :: Maybe Natural
dayOfMonth :: Maybe Natural
$sel:minuteOfHour:MaintenanceStartTime' :: MaintenanceStartTime -> Natural
$sel:hourOfDay:MaintenanceStartTime' :: MaintenanceStartTime -> Natural
$sel:dayOfWeek:MaintenanceStartTime' :: MaintenanceStartTime -> Maybe Natural
$sel:dayOfMonth:MaintenanceStartTime' :: MaintenanceStartTime -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
dayOfMonth
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
dayOfWeek
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
hourOfDay
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
minuteOfHour

instance Prelude.NFData MaintenanceStartTime where
  rnf :: MaintenanceStartTime -> ()
rnf MaintenanceStartTime' {Natural
Maybe Natural
minuteOfHour :: Natural
hourOfDay :: Natural
dayOfWeek :: Maybe Natural
dayOfMonth :: Maybe Natural
$sel:minuteOfHour:MaintenanceStartTime' :: MaintenanceStartTime -> Natural
$sel:hourOfDay:MaintenanceStartTime' :: MaintenanceStartTime -> Natural
$sel:dayOfWeek:MaintenanceStartTime' :: MaintenanceStartTime -> Maybe Natural
$sel:dayOfMonth:MaintenanceStartTime' :: MaintenanceStartTime -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
dayOfMonth
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
dayOfWeek
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
hourOfDay
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
minuteOfHour