remove duration from Schedule
This commit is contained in:
parent
2b6747b6a2
commit
3621044203
2 changed files with 28 additions and 40 deletions
|
@ -9,30 +9,42 @@ module Types.ScheduledActivity where
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
import Utility.Scheduled
|
import Utility.Scheduled
|
||||||
|
import Utility.HumanTime
|
||||||
import Types.UUID
|
import Types.UUID
|
||||||
|
|
||||||
data ScheduledActivity
|
data ScheduledActivity
|
||||||
= ScheduledSelfFsck Schedule
|
= ScheduledSelfFsck Schedule Duration
|
||||||
| ScheduledRemoteFsck UUID Schedule
|
| ScheduledRemoteFsck UUID Schedule Duration
|
||||||
deriving (Eq, Read, Show, Ord)
|
deriving (Eq, Read, Show, Ord)
|
||||||
|
|
||||||
|
getSchedule :: ScheduledActivity -> Schedule
|
||||||
|
getSchedule (ScheduledSelfFsck s _) = s
|
||||||
|
getSchedule (ScheduledRemoteFsck _ s _) = s
|
||||||
|
|
||||||
|
getDuration :: ScheduledActivity -> Duration
|
||||||
|
getDuration (ScheduledSelfFsck _ d) = d
|
||||||
|
getDuration (ScheduledRemoteFsck _ _ d) = d
|
||||||
|
|
||||||
fromScheduledActivity :: ScheduledActivity -> String
|
fromScheduledActivity :: ScheduledActivity -> String
|
||||||
fromScheduledActivity (ScheduledSelfFsck s) =
|
fromScheduledActivity (ScheduledSelfFsck s d) = unwords
|
||||||
"fsck self " ++ fromSchedule s
|
[ "fsck self", fromDuration d, fromSchedule s ]
|
||||||
fromScheduledActivity (ScheduledRemoteFsck u s) =
|
fromScheduledActivity (ScheduledRemoteFsck u s d) = unwords
|
||||||
"fsck " ++ fromUUID u ++ fromSchedule s
|
[ "fsck", fromUUID u, fromDuration d, fromSchedule s ]
|
||||||
|
|
||||||
toScheduledActivity :: String -> Maybe ScheduledActivity
|
toScheduledActivity :: String -> Maybe ScheduledActivity
|
||||||
toScheduledActivity = eitherToMaybe . parseScheduledActivity
|
toScheduledActivity = eitherToMaybe . parseScheduledActivity
|
||||||
|
|
||||||
parseScheduledActivity :: String -> Either String ScheduledActivity
|
parseScheduledActivity :: String -> Either String ScheduledActivity
|
||||||
parseScheduledActivity s = case words s of
|
parseScheduledActivity s = case words s of
|
||||||
("fsck":"self":rest) -> qualified $ ScheduledSelfFsck
|
("fsck":"self":d:rest) -> qualified $ ScheduledSelfFsck
|
||||||
<$> parseSchedule (unwords rest)
|
<$> parseSchedule (unwords rest)
|
||||||
("fsck":u:rest) -> qualified $ ScheduledRemoteFsck
|
<*> getduration d
|
||||||
|
("fsck":u:d:rest) -> qualified $ ScheduledRemoteFsck
|
||||||
<$> pure (toUUID u)
|
<$> pure (toUUID u)
|
||||||
<*> parseSchedule (unwords rest)
|
<*> parseSchedule (unwords rest)
|
||||||
|
<*> getduration d
|
||||||
_ -> qualified $ Left "unknown activity"
|
_ -> qualified $ Left "unknown activity"
|
||||||
where
|
where
|
||||||
qualified (Left e) = Left $ e ++ " in \"" ++ s ++ "\""
|
qualified (Left e) = Left $ e ++ " in \"" ++ s ++ "\""
|
||||||
qualified v = v
|
qualified v = v
|
||||||
|
getduration d = maybe (Left $ "failed to parse duration \""++d++"\"") Right (parseDuration d)
|
||||||
|
|
|
@ -9,7 +9,7 @@ module Utility.Scheduled (
|
||||||
Schedule(..),
|
Schedule(..),
|
||||||
Recurrance(..),
|
Recurrance(..),
|
||||||
ScheduledTime(..),
|
ScheduledTime(..),
|
||||||
Duration(..),
|
NextTime(..),
|
||||||
nextTime,
|
nextTime,
|
||||||
fromSchedule,
|
fromSchedule,
|
||||||
toSchedule,
|
toSchedule,
|
||||||
|
@ -28,7 +28,7 @@ import Data.Time.Calendar.OrdinalDate
|
||||||
import Data.Tuple.Utils
|
import Data.Tuple.Utils
|
||||||
|
|
||||||
{- Some sort of scheduled event. -}
|
{- Some sort of scheduled event. -}
|
||||||
data Schedule = Schedule Recurrance ScheduledTime Duration
|
data Schedule = Schedule Recurrance ScheduledTime
|
||||||
deriving (Eq, Read, Show, Ord)
|
deriving (Eq, Read, Show, Ord)
|
||||||
|
|
||||||
data Recurrance
|
data Recurrance
|
||||||
|
@ -53,9 +53,6 @@ data ScheduledTime
|
||||||
type Hour = Int
|
type Hour = Int
|
||||||
type Minute = Int
|
type Minute = Int
|
||||||
|
|
||||||
data Duration = MinutesDuration Int
|
|
||||||
deriving (Eq, Read, Show, Ord)
|
|
||||||
|
|
||||||
{- Next time a Schedule should take effect. The NextTimeWindow is used
|
{- Next time a Schedule should take effect. The NextTimeWindow is used
|
||||||
- when a Schedule is allowed to start at some point within the window. -}
|
- when a Schedule is allowed to start at some point within the window. -}
|
||||||
data NextTime
|
data NextTime
|
||||||
|
@ -72,7 +69,7 @@ nextTime schedule lasttime = do
|
||||||
{- Calculate the next time that fits a Schedule, based on the
|
{- Calculate the next time that fits a Schedule, based on the
|
||||||
- last time it occurred, and the current time. -}
|
- last time it occurred, and the current time. -}
|
||||||
calcNextTime :: Schedule -> Maybe LocalTime -> LocalTime -> Maybe NextTime
|
calcNextTime :: Schedule -> Maybe LocalTime -> LocalTime -> Maybe NextTime
|
||||||
calcNextTime (Schedule recurrance scheduledtime _duration) lasttime currenttime
|
calcNextTime (Schedule recurrance scheduledtime) lasttime currenttime
|
||||||
| scheduledtime == AnyTime = do
|
| scheduledtime == AnyTime = do
|
||||||
start <- findfromtoday
|
start <- findfromtoday
|
||||||
return $ NextTimeWindow
|
return $ NextTimeWindow
|
||||||
|
@ -196,22 +193,11 @@ toScheduledTime s =
|
||||||
let (h, m) = separate (== ':') s
|
let (h, m) = separate (== ':') s
|
||||||
in SpecificTime <$> readish h <*> readish m
|
in SpecificTime <$> readish h <*> readish m
|
||||||
|
|
||||||
fromDuration :: Duration -> String
|
|
||||||
fromDuration (MinutesDuration n) = show n ++ " minutes"
|
|
||||||
|
|
||||||
toDuration :: String -> Maybe Duration
|
|
||||||
toDuration s = case words s of
|
|
||||||
(n:"minutes":[]) -> MinutesDuration <$> readish n
|
|
||||||
(n:"minute":[]) -> MinutesDuration <$> readish n
|
|
||||||
_ -> Nothing
|
|
||||||
|
|
||||||
fromSchedule :: Schedule -> String
|
fromSchedule :: Schedule -> String
|
||||||
fromSchedule (Schedule recurrance scheduledtime duration) = unwords
|
fromSchedule (Schedule recurrance scheduledtime) = unwords
|
||||||
[ fromRecurrance recurrance
|
[ fromRecurrance recurrance
|
||||||
, "at"
|
, "at"
|
||||||
, fromScheduledTime scheduledtime
|
, fromScheduledTime scheduledtime
|
||||||
, "for"
|
|
||||||
, fromDuration duration
|
|
||||||
]
|
]
|
||||||
|
|
||||||
toSchedule :: String -> Maybe Schedule
|
toSchedule :: String -> Maybe Schedule
|
||||||
|
@ -223,22 +209,14 @@ parseSchedule s = do
|
||||||
(toRecurrance recurrance)
|
(toRecurrance recurrance)
|
||||||
t <- maybe (Left $ "bad time of day: " ++ scheduledtime) Right
|
t <- maybe (Left $ "bad time of day: " ++ scheduledtime) Right
|
||||||
(toScheduledTime scheduledtime)
|
(toScheduledTime scheduledtime)
|
||||||
d <- maybe (Left $ "bad duration: " ++ duration) Right
|
Right $ Schedule r t
|
||||||
(toDuration duration)
|
|
||||||
Right $ Schedule r t d
|
|
||||||
where
|
where
|
||||||
ws = words s
|
(rws, tws) = separate (== "at") (words s)
|
||||||
(rws, ws') = separate (== "at") ws
|
|
||||||
(tws, dws) = separate (== "for") ws'
|
|
||||||
recurrance = unwords rws
|
recurrance = unwords rws
|
||||||
scheduledtime = unwords tws
|
scheduledtime = unwords tws
|
||||||
duration = unwords dws
|
|
||||||
|
|
||||||
instance Arbitrary Schedule where
|
instance Arbitrary Schedule where
|
||||||
arbitrary = Schedule <$> arbitrary <*> arbitrary <*> arbitrary
|
arbitrary = Schedule <$> arbitrary <*> arbitrary
|
||||||
|
|
||||||
instance Arbitrary Duration where
|
|
||||||
arbitrary = MinutesDuration <$> nonNegative arbitrary
|
|
||||||
|
|
||||||
instance Arbitrary ScheduledTime where
|
instance Arbitrary ScheduledTime where
|
||||||
arbitrary = oneof
|
arbitrary = oneof
|
||||||
|
@ -265,6 +243,4 @@ instance Arbitrary Recurrance where
|
||||||
]
|
]
|
||||||
|
|
||||||
prop_schedule_roundtrips :: Schedule -> Bool
|
prop_schedule_roundtrips :: Schedule -> Bool
|
||||||
prop_schedule_roundtrips s = case toSchedule $ fromSchedule s of
|
prop_schedule_roundtrips s = toSchedule (fromSchedule s) == Just s
|
||||||
Just s' | s == s' -> True
|
|
||||||
_ -> False
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue