add support for weekly, monthly, and yearly schedules that run on no specific day

This commit is contained in:
Joey Hess 2013-10-15 13:05:41 -04:00
parent 7b82f431ba
commit e5e4b80b09
3 changed files with 145 additions and 80 deletions

View file

@ -82,18 +82,18 @@ runFsckForm new activity = case activity of
recurrances :: [(Text, Recurrance)] recurrances :: [(Text, Recurrance)]
recurrances = ensurevalue r (T.pack $ fromRecurrance r) $ recurrances = ensurevalue r (T.pack $ fromRecurrance r) $
[ ("every day", Daily) [ ("every day", Daily)
, ("every Sunday", Weekly 1) , ("every Sunday", Weekly $ Just 1)
, ("every Monday", Weekly 2) , ("every Monday", Weekly $ Just 2)
, ("every Tuesday", Weekly 3) , ("every Tuesday", Weekly $ Just 3)
, ("every Wednesday", Weekly 4) , ("every Wednesday", Weekly $ Just 4)
, ("every Thursday", Weekly 5) , ("every Thursday", Weekly $ Just 5)
, ("every Friday", Weekly 6) , ("every Friday", Weekly $ Just 6)
, ("every Saturday", Weekly 7) , ("every Saturday", Weekly $ Just 7)
, ("monthly", Monthly 1) , ("monthly", Monthly Nothing)
, ("twice a month", Divisible 2 (Weekly 1)) , ("twice a month", Divisible 2 (Weekly Nothing))
, ("yearly", Yearly 1) , ("yearly", Yearly Nothing)
, ("twice a year", Divisible 6 (Monthly 1)) , ("twice a year", Divisible 6 (Monthly Nothing))
, ("quarterly", Divisible 4 (Monthly 1)) , ("quarterly", Divisible 4 (Monthly Nothing))
] ]
ensurevalue v desc l = case M.lookup v (M.fromList $ map (\(x,y) -> (y,x)) l) of ensurevalue v desc l = case M.lookup v (M.fromList $ map (\(x,y) -> (y,x)) l) of
Just _ -> l Just _ -> l

View file

@ -38,9 +38,9 @@ data Schedule = Schedule Recurrance ScheduledTime
data Recurrance data Recurrance
= Daily = Daily
| Weekly WeekDay | Weekly (Maybe WeekDay)
| Monthly MonthDay | Monthly (Maybe MonthDay)
| Yearly YearDay | Yearly (Maybe YearDay)
-- Days, Weeks, or Months of the year evenly divisible by a number. -- Days, Weeks, or Months of the year evenly divisible by a number.
-- (Divisible Year is years evenly divisible by a number.) -- (Divisible Year is years evenly divisible by a number.)
| Divisible Int Recurrance | Divisible Int Recurrance
@ -65,6 +65,10 @@ data NextTime
| NextTimeWindow LocalTime LocalTime | NextTimeWindow LocalTime LocalTime
deriving (Eq, Read, Show) deriving (Eq, Read, Show)
startTime :: NextTime -> LocalTime
startTime (NextTimeExactly t) = t
startTime (NextTimeWindow t _) = t
nextTime :: Schedule -> Maybe LocalTime -> IO (Maybe NextTime) nextTime :: Schedule -> Maybe LocalTime -> IO (Maybe NextTime)
nextTime schedule lasttime = do nextTime schedule lasttime = do
now <- getCurrentTime now <- getCurrentTime
@ -76,77 +80,127 @@ nextTime schedule lasttime = do
calcNextTime :: Schedule -> Maybe LocalTime -> LocalTime -> Maybe NextTime calcNextTime :: Schedule -> Maybe LocalTime -> LocalTime -> Maybe NextTime
calcNextTime (Schedule recurrance scheduledtime) lasttime currenttime calcNextTime (Schedule recurrance scheduledtime) lasttime currenttime
| scheduledtime == AnyTime = do | scheduledtime == AnyTime = do
start <- findfromtoday True next <- findfromtoday True
return $ NextTimeWindow return $ case next of
start NextTimeWindow _ _ -> next
(LocalTime (localDay start) (TimeOfDay 23 59 0)) NextTimeExactly t -> window (localDay t) (localDay t)
| otherwise = NextTimeExactly <$> findfromtoday False | otherwise = NextTimeExactly . startTime <$> findfromtoday False
where where
findfromtoday anytime = findfromtoday anytime = findfrom recurrance afterday today
LocalTime <$> nextday <*> pure nexttime
where where
nextday = findnextday recurrance afterday today
today = localDay currenttime today = localDay currenttime
afterday = sameaslastday || toolatetoday afterday = sameaslastday || toolatetoday
toolatetoday = not anytime && localTimeOfDay currenttime >= nexttime toolatetoday = not anytime && localTimeOfDay currenttime >= nexttime
sameaslastday = (localDay <$> lasttime) == Just today sameaslastday = lastday == Just today
lastday = localDay <$> lasttime
nexttime = case scheduledtime of nexttime = case scheduledtime of
AnyTime -> TimeOfDay 0 0 0 AnyTime -> TimeOfDay 0 0 0
SpecificTime h m -> TimeOfDay h m 0 SpecificTime h m -> TimeOfDay h m 0
findnextday r afterday day = case r of exactly d = NextTimeExactly $ LocalTime d nexttime
window startd endd = NextTimeWindow
(LocalTime startd nexttime)
(LocalTime endd (TimeOfDay 23 59 0))
findfrom r afterday day = case r of
Daily Daily
| afterday -> Just $ addDays 1 day | afterday -> Just $ exactly $ addDays 1 day
| otherwise -> Just day | otherwise -> Just $ exactly day
Weekly w Weekly Nothing
| afterday -> skip 1
| otherwise -> case (wday <$> lastday, wday day) of
(Nothing, _) -> Just $ window day (addDays 6 day)
(Just old, curr)
| old == curr -> Just $ window day (addDays 6 day)
| otherwise -> skip 1
Monthly Nothing
| afterday -> skip 1
| maybe True (\old -> mnum day > mday old && mday day >= (mday old `mod` minmday)) lastday ->
-- Window only covers current month,
-- in case there is a Divisible requirement.
Just $ window day (endOfMonth day)
| otherwise -> skip 1
Yearly Nothing
| afterday -> skip 1
| maybe True (\old -> ynum day > ynum old && yday day >= (yday old `mod` minyday)) lastday ->
Just $ window day (endOfYear day)
| otherwise -> skip 1
Weekly (Just w)
| w < 0 || w > maxwday -> Nothing | w < 0 || w > maxwday -> Nothing
| w == wday day -> if afterday | w == wday day -> if afterday
then Just $ addDays 7 day then Just $ exactly $ addDays 7 day
else Just day else Just $ exactly day
| otherwise -> Just $ | otherwise -> Just $ exactly $
addDays (fromIntegral $ (w - wday day) `mod` 7) day addDays (fromIntegral $ (w - wday day) `mod` 7) day
Monthly m Monthly (Just m)
| m < 0 || m > maxmday -> Nothing | m < 0 || m > maxmday -> Nothing
-- TODO can be done more efficiently than recursing -- TODO can be done more efficiently than recursing
| m == mday day -> if afterday | m == mday day -> if afterday
then findnextday r False (addDays 1 day) then skip 1
else Just day else Just $ exactly day
| otherwise -> findnextday r False (addDays 1 day) | otherwise -> skip 1
Yearly y Yearly (Just y)
| y < 0 || y > maxyday -> Nothing | y < 0 || y > maxyday -> Nothing
| y == yday day -> if afterday | y == yday day -> if afterday
then findnextday r False (addDays 365 day) then skip 365
else Just day else Just $ exactly day
| otherwise -> findnextday r False (addDays 1 day) | otherwise -> skip 1
Divisible n r'@Daily -> handlediv n r' yday (Just maxyday) Divisible n r'@Daily -> handlediv n r' yday (Just maxyday)
Divisible n r'@(Weekly _) -> handlediv n r' wnum (Just maxwnum) Divisible n r'@(Weekly _) -> handlediv n r' wnum (Just maxwnum)
Divisible n r'@(Monthly _) -> handlediv n r' mnum (Just maxmnum) Divisible n r'@(Monthly _) -> handlediv n r' mnum (Just maxmnum)
Divisible n r'@(Yearly _) -> handlediv n r' year Nothing Divisible n r'@(Yearly _) -> handlediv n r' ynum Nothing
Divisible _ r'@(Divisible _ _) -> findnextday r' afterday day Divisible _ r'@(Divisible _ _) -> findfrom r' afterday day
where where
skip n = findfrom r False (addDays n day)
handlediv n r' getval mmax handlediv n r' getval mmax
| n > 0 && maybe True (n <=) mmax = | n > 0 && maybe True (n <=) mmax =
findnextdaywhere r' (divisible n . getval) afterday day findfromwhere r' (divisible n . getval) afterday day
| otherwise = Nothing | otherwise = Nothing
findnextdaywhere r p afterday day findfromwhere r p afterday day
| maybe True p d = d | maybe True (p . getday) next = next
| otherwise = maybe d (findnextdaywhere r p True) d | otherwise = maybe Nothing (findfromwhere r p True . getday) next
where where
d = findnextday r afterday day next = findfrom r afterday day
getday = localDay . startTime
divisible n v = v `rem` n == 0 divisible n v = v `rem` n == 0
-- extracting various quantities from a Day endOfMonth :: Day -> Day
wday = thd3 . toWeekDate endOfMonth day =
wnum = snd3 . toWeekDate let (y,m,_d) = toGregorian day
mday = thd3 . toGregorian in fromGregorian y m (gregorianMonthLength y m)
mnum = snd3 . toGregorian
yday = snd . toOrdinalDate
year = fromIntegral . fst . toOrdinalDate
maxyday = 366 -- with leap days endOfYear :: Day -> Day
maxwnum = 53 -- some years have more than 52 endOfYear day =
maxmday = 31 let (y,_m,_d) = toGregorian day
maxmnum = 12 in endOfMonth (fromGregorian y maxmnum 1)
maxwday = 7
-- extracting various quantities from a Day
wday :: Day -> Int
wday = thd3 . toWeekDate
wnum :: Day -> Int
wnum = snd3 . toWeekDate
mday :: Day -> Int
mday = thd3 . toGregorian
mnum :: Day -> Int
mnum = snd3 . toGregorian
yday :: Day -> Int
yday = snd . toOrdinalDate
ynum :: Day -> Int
ynum = fromIntegral . fst . toOrdinalDate
{- Calendar max and mins. -}
maxyday :: Int
maxyday = 366 -- with leap days
minyday :: Int
minyday = 365
maxwnum :: Int
maxwnum = 53 -- some years have more than 52
maxmday :: Int
maxmday = 31
minmday :: Int
minmday = 28
maxmnum :: Int
maxmnum = 12
maxwday :: Int
maxwday = 7
fromRecurrance :: Recurrance -> String fromRecurrance :: Recurrance -> String
fromRecurrance (Divisible n r) = fromRecurrance (Divisible n r) =
@ -160,28 +214,40 @@ fromRecurrance' a (Monthly n) = onday n (a "month")
fromRecurrance' a (Yearly n) = onday n (a "year") fromRecurrance' a (Yearly n) = onday n (a "year")
fromRecurrance' a (Divisible _n r) = fromRecurrance' a r -- not used fromRecurrance' a (Divisible _n r) = fromRecurrance' a r -- not used
onday :: Int -> String -> String onday :: Maybe Int -> String -> String
onday n s = "on day " ++ show n ++ " of " ++ s onday (Just n) s = "on day " ++ show n ++ " of " ++ s
onday Nothing s = s
toRecurrance :: String -> Maybe Recurrance toRecurrance :: String -> Maybe Recurrance
toRecurrance s = case words s of toRecurrance s = case words s of
("every":"day":[]) -> Just Daily ("every":"day":[]) -> Just Daily
("on":"day":sd:"of":"every":something:[]) -> parse something sd ("on":"day":sd:"of":"every":something:[]) -> withday sd something
("every":something:[]) -> noday something
("days":"divisible":"by":sn:[]) -> ("days":"divisible":"by":sn:[]) ->
Divisible <$> getdivisor sn <*> pure Daily Divisible <$> getdivisor sn <*> pure Daily
("on":"day":sd:"of":something:"divisible":"by":sn:[]) -> ("on":"day":sd:"of":something:"divisible":"by":sn:[]) ->
Divisible Divisible
<$> getdivisor sn <$> getdivisor sn
<*> parse something sd <*> withday sd something
("every":something:"divisible":"by":sn:[]) ->
Divisible
<$> getdivisor sn
<*> noday something
_ -> Nothing _ -> Nothing
where where
parse "week" sd = withday Weekly sd constructor "week" = Just Weekly
parse "month" sd = withday Monthly sd constructor "month" = Just Monthly
parse "year" sd = withday Yearly sd constructor "year" = Just Yearly
parse v sd constructor u
| "s" `isSuffixOf` v = parse (reverse $ drop 1 $ reverse v) sd | "s" `isSuffixOf` u = constructor $ reverse $ drop 1 $ reverse u
| otherwise = Nothing | otherwise = Nothing
withday c sd = c <$> readish sd withday sd u = do
c <- constructor u
d <- readish sd
Just $ c (Just d)
noday u = do
c <- constructor u
Just $ c Nothing
getdivisor sn = do getdivisor sn = do
n <- readish sn n <- readish sn
if n > 0 if n > 0
@ -255,18 +321,23 @@ instance Arbitrary ScheduledTime where
instance Arbitrary Recurrance where instance Arbitrary Recurrance where
arbitrary = oneof arbitrary = oneof
[ pure Daily [ pure Daily
, Weekly <$> nonNegative arbitrary , Weekly <$> arbday
, Monthly <$> nonNegative arbitrary , Monthly <$> arbday
, Yearly <$> nonNegative arbitrary , Yearly <$> arbday
, Divisible , Divisible
<$> positive arbitrary <$> positive arbitrary
<*> oneof -- no nested Divisibles <*> oneof -- no nested Divisibles
[ pure Daily [ pure Daily
, Weekly <$> nonNegative arbitrary , Weekly <$> arbday
, Monthly <$> nonNegative arbitrary , Monthly <$> arbday
, Yearly <$> nonNegative arbitrary , Yearly <$> arbday
] ]
] ]
where
arbday = oneof
[ Just <$> nonNegative arbitrary
, pure Nothing
]
prop_schedule_roundtrips :: Schedule -> Bool prop_schedule_roundtrips :: Schedule -> Bool
prop_schedule_roundtrips s = toSchedule (fromSchedule s) == Just s prop_schedule_roundtrips s = toSchedule (fromSchedule s) == Just s

View file

@ -42,12 +42,6 @@ prompt the user to eg, connect a drive containing it. Or perhaps this is a
special case of a general problem, and the webapp should prompt the user special case of a general problem, and the webapp should prompt the user
when any desired file is available on a remote that's not mounted? when any desired file is available on a remote that's not mounted?
TODO: Enhance the Recurrance type to be able to do eg, events that run
once per month on any day, or once per year, or once per week. This
would be especially useful for removable drives, which might not be
plugged in on the 1st of the month. This should be the default in the
webapp (it's already worded to suggest this.)
## git-annex-shell remote fsck ## git-annex-shell remote fsck
TODO: git-annex-shell fsck support, which would allow cheap fast fscks TODO: git-annex-shell fsck support, which would allow cheap fast fscks