diff options
Diffstat (limited to 'lib/Postdelay/TimeSpec.hs')
-rw-r--r-- | lib/Postdelay/TimeSpec.hs | 92 |
1 files changed, 71 insertions, 21 deletions
diff --git a/lib/Postdelay/TimeSpec.hs b/lib/Postdelay/TimeSpec.hs index 4a32317..9361057 100644 --- a/lib/Postdelay/TimeSpec.hs +++ b/lib/Postdelay/TimeSpec.hs | |||
@@ -9,6 +9,7 @@ module Postdelay.TimeSpec | |||
9 | 9 | ||
10 | import Postdelay.TimeSpec.Utils | 10 | import Postdelay.TimeSpec.Utils |
11 | import Postdelay.TimeSpec.Units | 11 | import Postdelay.TimeSpec.Units |
12 | import Postdelay.PrioMap | ||
12 | 13 | ||
13 | import Text.Megaparsec | 14 | import Text.Megaparsec |
14 | 15 | ||
@@ -19,47 +20,67 @@ import Control.Exception (IOException) | |||
19 | import Control.Monad.Catch hiding (try) | 20 | import Control.Monad.Catch hiding (try) |
20 | import Control.Monad.RWS hiding ((<>)) | 21 | import Control.Monad.RWS hiding ((<>)) |
21 | 22 | ||
23 | import Data.Functor | ||
22 | import Data.Bool | 24 | import Data.Bool |
23 | import Data.Semigroup hiding (option) | 25 | import Data.Semigroup hiding (option) |
24 | import Data.Monoid (Endo(..)) | 26 | import Data.Monoid (Endo(..)) |
25 | import Data.Foldable | 27 | import Data.Foldable |
26 | import Data.VectorSpace | 28 | import Data.VectorSpace |
29 | import Data.Maybe | ||
27 | 30 | ||
28 | import Data.Time | 31 | import Data.Time as Time hiding (months) |
32 | import Data.Time.Calendar.WeekDate | ||
29 | import Data.Time.Lens | 33 | import Data.Time.Lens |
30 | import Data.Time.Zones | 34 | import Data.Time.Zones |
31 | 35 | ||
32 | 36 | ||
37 | data ModPrio = Offset | Assign | Shift | Default | ||
38 | deriving (Eq, Ord, Enum, Bounded, Show) | ||
39 | |||
40 | |||
33 | seconds' :: Timeable t => Lens' t Time | 41 | seconds' :: Timeable t => Lens' t Time |
34 | seconds' = seconds . iso (% Second) (# Second) | 42 | seconds' = seconds . iso (% Second) (# Second) |
35 | 43 | ||
36 | utcOffset :: Iso' TimeZone Time | 44 | utcOffset :: Iso' TimeZone Time |
37 | utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute)) | 45 | utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute)) |
38 | 46 | ||
39 | shiftBack :: MonadState LocalTime m => Time -> m a -> m a | 47 | weekDate :: Dateable t => Lens' t (Integer, Int, Int) |
40 | shiftBack by mod = join $ shiftBack' <$> get <*> mod <*> get | 48 | weekDate = date . iso toWeekDate (\(y, w, d) -> fromWeekDate y w d) |
41 | where | 49 | |
42 | shiftBack' prev ret new | 50 | shiftBack :: (MonadReader LocalTime m, MonadWriter (PrioEndo ModPrio LocalTime) m) |
43 | | new < prev = ret <$ (flexDT.seconds' %= (^+^) by) | 51 | => Time -> PrioEndo ModPrio LocalTime -> m () |
44 | | otherwise = pure ret | 52 | shiftBack by mod@(view (prioEndo._Endo) -> modE) = do |
53 | tell mod | ||
54 | |||
55 | prev <- ask | ||
56 | new <- asks modE | ||
57 | case new <= prev of | ||
58 | True -> scribe (prio Shift) . Just . Endo $ flexDT.seconds' %~ ((^+^) by) | ||
59 | False -> return () | ||
60 | |||
61 | mod' :: ModPrio -> ASetter' LocalTime a -> a -> PrioEndo ModPrio LocalTime | ||
62 | mod' priority setter val = mempty & prio priority .~ (Just . Endo $ set setter val) | ||
63 | |||
64 | scribeMod :: MonadWriter (PrioEndo ModPrio LocalTime) m => ModPrio -> ASetter' LocalTime a -> a -> m () | ||
65 | scribeMod priority setter val = tell $ mod' priority setter val | ||
45 | 66 | ||
46 | 67 | ||
47 | timeSpec :: forall s m. StringParser s m => m (Endo LocalTime) | 68 | timeSpec :: forall s m. StringParser s m => m (Endo LocalTime) |
48 | timeSpec = label "Relative time specification" $ | 69 | timeSpec = label "Relative time specification" $ view prioEndo <$> choice |
49 | choice [ flip (<>) <$> lexeme specBase <*> option mempty (offsets True) | 70 | [ flip (<>) <$> lexeme specBase <*> option mempty (offsets True) |
50 | , lexeme (string' "now") *> offsets True | 71 | , lexeme (string' "now") *> offsets True |
51 | , offsets False | 72 | , offsets False |
52 | ] | 73 | ] |
53 | where | 74 | where |
54 | specBase = toEndo <$> mkGramSepBy spaces [ timeOfDay | 75 | specBase = toEndo <$> mkGramSepBy spaces [ timeOfDay |
55 | , dateSpec | 76 | , dateSpec |
56 | ] | 77 | ] |
57 | 78 | ||
58 | toEndo :: [RWS LocalTime () LocalTime a] -> Endo LocalTime | 79 | toEndo :: [RWS LocalTime (PrioEndo ModPrio LocalTime) () ()] -> PrioEndo ModPrio LocalTime |
59 | toEndo (sequence -> act) = Endo $ \t -> fst $ execRWS act t t | 80 | toEndo (sequence -> act) = mempty & prios .@~ (\i -> Just . Endo $ \t -> maybe t (($ t) . appEndo) . view (prio i) . snd $ execRWS act t ()) |
60 | 81 | ||
61 | timeOfDay, dateSpec :: StringParser s m => m (RWS LocalTime () LocalTime ()) | 82 | timeOfDay, dateSpec :: StringParser s m => m (RWS LocalTime (PrioEndo ModPrio LocalTime) () ()) |
62 | timeOfDay = label "Time of day" $ shiftBack (1 % Day) . assign time <$> choice | 83 | timeOfDay = label "Time of day" $ withShift <$> choice |
63 | [ TimeOfDay 0 0 0 <$ string' "midnight" | 84 | [ TimeOfDay 0 0 0 <$ string' "midnight" |
64 | , TimeOfDay 12 0 0 <$ string' "noon" | 85 | , TimeOfDay 12 0 0 <$ string' "noon" |
65 | , TimeOfDay 16 0 0 <$ string' "teatime" | 86 | , TimeOfDay 16 0 0 <$ string' "teatime" |
@@ -75,22 +96,51 @@ timeOfDay = label "Time of day" $ shiftBack (1 % Day) . assign time <$> choice | |||
75 | spaceConsumer | 96 | spaceConsumer |
76 | amPm <- (0 <$ string' "am") <|> (12 <$ string' "pm") | 97 | amPm <- (0 <$ string' "am") <|> (12 <$ string' "pm") |
77 | return $ TimeOfDay (h + amPm) m s | 98 | return $ TimeOfDay (h + amPm) m s |
99 | , try $ do | ||
100 | h <- hour24 False | ||
101 | m <- option 0 $ char ':' *> minute False | ||
102 | s <- option 0 $ char ':' *> second False | ||
103 | return $ TimeOfDay h m s | ||
78 | ] | 104 | ] |
79 | where | 105 | where |
80 | hour12 pad = label "Modulus 12 hour" . fmap (flip mod 12) . boundedNatural pad $ 1 <=..<= 12 | 106 | hour12 pad = label "Modulus 12 hour" . fmap (flip mod 12) . boundedNatural pad $ 1 <=..<= 12 |
81 | hour24 pad = label "Modulus 24 hour" . boundedNatural pad $ 0 <=..< 24 | 107 | hour24 pad = label "Modulus 24 hour" . boundedNatural pad $ 0 <=..< 24 |
82 | minute pad = label "Minute" . boundedNatural pad $ 0 <=..< 60 | 108 | minute pad = label "Minute" . boundedNatural pad $ 0 <=..< 60 |
83 | second pad = label "Second" . boundedRational pad $ 0 <=..< 61 | 109 | second pad = label "Second" . boundedRational pad $ 0 <=..< 61 |
110 | |||
111 | withShift :: TimeOfDay -> RWS LocalTime (PrioEndo ModPrio LocalTime) () () | ||
112 | withShift = shiftBack (1 % Day) . mod' Assign time | ||
84 | 113 | ||
85 | dateSpec = label "Date" $ (date <~) <$> choice | 114 | dateSpec = label "Date" $ choice |
86 | [ view date <$ string' "today" | 115 | [ (scribeMod Assign date =<< view date) <$ string' "today" |
87 | , views date succ <$ string' "tomorrow" | 116 | , (scribeMod Assign date =<< views date succ) <$ string' "tomorrow" |
117 | , do | ||
118 | string' "next" | ||
119 | spaces | ||
120 | choice | ||
121 | [ string' "day" $> do | ||
122 | scribeMod Assign (flexDT.date.days) =<< views (date.days) succ | ||
123 | scribeMod Default time midnight | ||
124 | , string' "week" $> do | ||
125 | scribeMod Assign (flexDT.date.days) =<< views (date.days) (+ 7) | ||
126 | scribeMod Assign (weekDate._3) 1 | ||
127 | scribeMod Default time midnight | ||
128 | , string' "month" $> do | ||
129 | scribeMod Assign (flexDT.date.months) =<< views (date.months) succ | ||
130 | scribeMod Assign (date.days) 1 | ||
131 | scribeMod Default time midnight | ||
132 | , string' "year" $> do | ||
133 | scribeMod Assign (flexDT.date.years) =<< views (date.years) succ | ||
134 | scribeMod Assign (date.months) 1 | ||
135 | scribeMod Assign (date.days) 1 | ||
136 | scribeMod Default time midnight | ||
137 | ] | ||
88 | ] | 138 | ] |
89 | 139 | ||
90 | offsets :: forall s m. StringParser s m | 140 | offsets :: forall s m. StringParser s m |
91 | => Bool -- ^ Require sign on first offset? | 141 | => Bool -- ^ Require sign on first offset? |
92 | -> m (Endo LocalTime) | 142 | -> m (PrioEndo ModPrio LocalTime) |
93 | offsets reqSgn = fmap fold $ (:) <$> offset reqSgn <*> many (offset False) | 143 | offsets reqSgn = fmap (foldMap . review $ prioEndo' Offset) $ (:) <$> offset reqSgn <*> many (offset False) |
94 | where | 144 | where |
95 | asOffset :: Time -> Endo LocalTime | 145 | asOffset :: Time -> Endo LocalTime |
96 | asOffset by = Endo $ flexDT.seconds' %~ (^+^ by) | 146 | asOffset by = Endo $ flexDT.seconds' %~ (^+^ by) |