module Saturn.Unstable.Constant where
import qualified Data.Maybe as Maybe
import qualified Saturn.Unstable.Type.Day as Day
import qualified Saturn.Unstable.Type.Element as Element
import qualified Saturn.Unstable.Type.Field as Field
import qualified Saturn.Unstable.Type.Hour as Hour
import qualified Saturn.Unstable.Type.Minute as Minute
import qualified Saturn.Unstable.Type.Month as Month
import qualified Saturn.Unstable.Type.Number as Number
import qualified Saturn.Unstable.Type.Schedule as Schedule
import qualified Saturn.Unstable.Type.Weekday as Weekday
import qualified Saturn.Unstable.Type.Wildcard as Wildcard
everyMinute :: Schedule.Schedule
everyMinute :: Schedule
everyMinute = forall a. a -> Maybe a -> a
Maybe.fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"Saturn.Unstable.Constant.everyMinute") forall a b. (a -> b) -> a -> b
$ do
let wildcard :: Field
wildcard = Either Wildcard (NonEmpty Element) -> Field
Field.fromEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ () -> Wildcard
Wildcard.fromUnit ()
Minute
minute <- Field -> Maybe Minute
Minute.fromField Field
wildcard
Hour
hour <- Field -> Maybe Hour
Hour.fromField Field
wildcard
Day
day <- Field -> Maybe Day
Day.fromField Field
wildcard
Month
month <- Field -> Maybe Month
Month.fromField Field
wildcard
Weekday
weekday <- Field -> Maybe Weekday
Weekday.fromField Field
wildcard
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Schedule.Schedule
{ minute :: Minute
Schedule.minute = Minute
minute,
hour :: Hour
Schedule.hour = Hour
hour,
day :: Day
Schedule.day = Day
day,
month :: Month
Schedule.month = Month
month,
weekday :: Weekday
Schedule.weekday = Weekday
weekday
}
hourly :: Schedule.Schedule
hourly :: Schedule
hourly = forall a. a -> Maybe a -> a
Maybe.fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"Saturn.Unstable.Constant.hourly") forall a b. (a -> b) -> a -> b
$ do
Minute
minute <-
Field -> Maybe Minute
Minute.fromField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Wildcard (NonEmpty Element) -> Field
Field.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Range Number -> Element
Element.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall a b. (a -> b) -> a -> b
$ Word8 -> Number
Number.fromWord8 Word8
0
forall (f :: * -> *) a. Applicative f => a -> f a
pure Schedule
everyMinute {minute :: Minute
Schedule.minute = Minute
minute}
daily :: Schedule.Schedule
daily :: Schedule
daily = forall a. a -> Maybe a -> a
Maybe.fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"Saturn.Unstable.Constant.daily") forall a b. (a -> b) -> a -> b
$ do
Hour
hour <-
Field -> Maybe Hour
Hour.fromField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Wildcard (NonEmpty Element) -> Field
Field.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Range Number -> Element
Element.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall a b. (a -> b) -> a -> b
$ Word8 -> Number
Number.fromWord8 Word8
0
forall (f :: * -> *) a. Applicative f => a -> f a
pure Schedule
hourly {hour :: Hour
Schedule.hour = Hour
hour}
weekly :: Schedule.Schedule
weekly :: Schedule
weekly = forall a. a -> Maybe a -> a
Maybe.fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"Saturn.Unstable.Constant.weekly") forall a b. (a -> b) -> a -> b
$ do
Weekday
weekday <-
Field -> Maybe Weekday
Weekday.fromField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Wildcard (NonEmpty Element) -> Field
Field.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Range Number -> Element
Element.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall a b. (a -> b) -> a -> b
$ Word8 -> Number
Number.fromWord8 Word8
0
forall (f :: * -> *) a. Applicative f => a -> f a
pure Schedule
daily {weekday :: Weekday
Schedule.weekday = Weekday
weekday}
monthly :: Schedule.Schedule
monthly :: Schedule
monthly = forall a. a -> Maybe a -> a
Maybe.fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"Saturn.Unstable.Constant.monthly") forall a b. (a -> b) -> a -> b
$ do
Day
day <-
Field -> Maybe Day
Day.fromField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Wildcard (NonEmpty Element) -> Field
Field.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Range Number -> Element
Element.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall a b. (a -> b) -> a -> b
$ Word8 -> Number
Number.fromWord8 Word8
1
forall (f :: * -> *) a. Applicative f => a -> f a
pure Schedule
daily {day :: Day
Schedule.day = Day
day}
yearly :: Schedule.Schedule
yearly :: Schedule
yearly = forall a. a -> Maybe a -> a
Maybe.fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"Saturn.Unstable.Constant.yearly") forall a b. (a -> b) -> a -> b
$ do
Month
month <-
Field -> Maybe Month
Month.fromField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Wildcard (NonEmpty Element) -> Field
Field.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Range Number -> Element
Element.fromEither
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
forall a b. (a -> b) -> a -> b
$ Word8 -> Number
Number.fromWord8 Word8
1
forall (f :: * -> *) a. Applicative f => a -> f a
pure Schedule
monthly {month :: Month
Schedule.month = Month
month}