diff options
Diffstat (limited to 'lib/Postdelay/TimeSpec.hs')
-rw-r--r-- | lib/Postdelay/TimeSpec.hs | 107 |
1 files changed, 88 insertions, 19 deletions
diff --git a/lib/Postdelay/TimeSpec.hs b/lib/Postdelay/TimeSpec.hs index c2ddc3f..21c48a4 100644 --- a/lib/Postdelay/TimeSpec.hs +++ b/lib/Postdelay/TimeSpec.hs | |||
@@ -48,15 +48,14 @@ weekDate :: Dateable t => Lens' t (Integer, Int, Int) | |||
48 | weekDate = date . iso toWeekDate (\(y, w, d) -> fromWeekDate y w d) | 48 | weekDate = date . iso toWeekDate (\(y, w, d) -> fromWeekDate y w d) |
49 | 49 | ||
50 | shiftBack :: (MonadReader LocalTime m, MonadWriter (PrioEndo ModPrio LocalTime) m) | 50 | shiftBack :: (MonadReader LocalTime m, MonadWriter (PrioEndo ModPrio LocalTime) m) |
51 | => Time -> PrioEndo ModPrio LocalTime -> m () | 51 | => Time -> m a -> m a |
52 | shiftBack by mod@(view (prioEndo._Endo) -> modE) = do | 52 | shiftBack by mod = do |
53 | tell mod | 53 | (result, modE) <- listen mod |
54 | |||
55 | prev <- ask | 54 | prev <- ask |
56 | new <- asks modE | 55 | new <- asks $ view (prioEndo._Endo) modE |
57 | case new <= prev of | 56 | when (new <= prev) $ |
58 | True -> scribe (prio Shift) . Just . Endo $ flexDT.seconds' %~ ((^+^) by) | 57 | scribe (prio Shift) . Just . Endo $ flexDT.seconds' %~ ((^+^) by) |
59 | False -> return () | 58 | return result |
60 | 59 | ||
61 | timeSpec :: forall s m. StringParser s m => m (Endo LocalTime) | 60 | timeSpec :: forall s m. StringParser s m => m (Endo LocalTime) |
62 | timeSpec = label "Relative time specification" $ view prioEndo <$> choice | 61 | timeSpec = label "Relative time specification" $ view prioEndo <$> choice |
@@ -65,8 +64,8 @@ timeSpec = label "Relative time specification" $ view prioEndo <$> choice | |||
65 | , offsets False | 64 | , offsets False |
66 | ] | 65 | ] |
67 | where | 66 | where |
68 | specBase = toEndo <$> mkGramSepBy spaces [ timeOfDay | 67 | specBase = toEndo <$> mkGramSepBy spaces [ dateSpec |
69 | , dateSpec | 68 | , timeOfDay |
70 | ] | 69 | ] |
71 | 70 | ||
72 | toEndo :: [RWS LocalTime (PrioEndo ModPrio LocalTime) () ()] -> PrioEndo ModPrio LocalTime | 71 | toEndo :: [RWS LocalTime (PrioEndo ModPrio LocalTime) () ()] -> PrioEndo ModPrio LocalTime |
@@ -102,34 +101,104 @@ timeOfDay = label "Time of day" $ withShift <$> choice | |||
102 | second pad = label "Second" . boundedRational pad $ 0 <=..< 61 | 101 | second pad = label "Second" . boundedRational pad $ 0 <=..< 61 |
103 | 102 | ||
104 | withShift :: TimeOfDay -> RWS LocalTime (PrioEndo ModPrio LocalTime) () () | 103 | withShift :: TimeOfDay -> RWS LocalTime (PrioEndo ModPrio LocalTime) () () |
105 | withShift = shiftBack (1 % Day) . mod' Assign time | 104 | withShift tod = shiftBack (1 % Day) $ scribe (prio' Assign . time) tod |
106 | mod' priority setter val = mempty & prio priority .~ (Just . Endo $ set setter val) | ||
107 | 105 | ||
108 | dateSpec = label "Date" $ choice | 106 | dateSpec = label "Date" $ (>> scribe (prio' Default . time) midnight) <$> choice |
109 | [ (scribe (prio' Assign . date) =<< view date) <$ string' "today" | 107 | [ (scribe (prio' Assign . date) =<< view date) <$ string' "today" |
110 | , (scribe (prio' Assign . date) =<< views date succ) <$ string' "tomorrow" | 108 | , (scribe (prio' Assign . date) =<< views date succ) <$ string' "tomorrow" |
111 | , do | 109 | , try $ do |
112 | string' "next" | 110 | string' "next" |
113 | spaces | 111 | spaces |
114 | choice | 112 | choice |
115 | [ string' "day" $> do | 113 | [ string' "day" $> do |
116 | scribe (prio' Assign . flexDT.date.days) =<< views (date.days) succ | 114 | scribe (prio' Assign . flexDT.date.days) =<< views (date.days) succ |
117 | scribe (prio' Default . time) midnight | ||
118 | , string' "week" $> do | 115 | , string' "week" $> do |
119 | scribe (prio' Assign . flexDT.date.days) =<< views (date.days) (+ 7) | 116 | scribe (prio' Assign . flexDT.date.days) =<< views (date.days) (+ 7) |
120 | scribe (prio' Assign . weekDate._3) 1 | 117 | scribe (prio' Assign . weekDate._3) 1 |
121 | scribe (prio' Default . time) midnight | ||
122 | , string' "month" $> do | 118 | , string' "month" $> do |
123 | scribe (prio' Assign . flexDT.date.months) =<< views (date.months) succ | 119 | scribe (prio' Assign . flexDT.date.months) =<< views (date.months) succ |
124 | scribe (prio' Assign . date.days) 1 | 120 | scribe (prio' Assign . date.days) 1 |
125 | scribe (prio' Default . time) midnight | ||
126 | , string' "year" $> do | 121 | , string' "year" $> do |
127 | scribe (prio' Assign . flexDT.date.years) =<< views (date.years) succ | 122 | scribe (prio' Assign . flexDT.date.years) =<< views (date.years) succ |
128 | scribe (prio' Assign . date.months) 1 | 123 | scribe (prio' Assign . date.months) 1 |
129 | scribe (prio' Assign . date.days) 1 | 124 | scribe (prio' Assign . date.days) 1 |
130 | scribe (prio' Default . time) midnight | ||
131 | ] | 125 | ] |
132 | ] | 126 | , try $ do |
127 | let daySuffix = optional $ choice [ string' "st", string' "nd", string' "rd", string' "th" ] | ||
128 | (m, d) <- choice [ try $ (,) <$> monthName <* spaces <*> dayNumber False <* daySuffix | ||
129 | , try $ flip (,) <$> dayNumber False <* daySuffix <* spaces <*> monthName | ||
130 | ] | ||
131 | y <- optional . try $ do | ||
132 | spaces | ||
133 | optional . lexeme $ char ',' | ||
134 | yearNumber <* lookAhead (spaces <|> eof) | ||
135 | return $ scribeDate y m d | ||
136 | , try $ do | ||
137 | m <- monthNumber False | ||
138 | char '/' | ||
139 | d <- dayNumber False | ||
140 | y <- optional . try $ char '/' *> yearNumber <* lookAhead (spaces <|> eof) | ||
141 | return $ scribeDate y m d | ||
142 | , try $ do | ||
143 | d <- dayNumber False | ||
144 | char '.' | ||
145 | m <- monthNumber False | ||
146 | y <- optional . try $ char '.' *> yearNumber <* lookAhead (spaces <|> eof) | ||
147 | return $ scribeDate y m d | ||
148 | , try $ do | ||
149 | (Just -> y) <- yearNumber | ||
150 | char '-' | ||
151 | m <- monthNumber True | ||
152 | char '-' | ||
153 | d <- dayNumber True | ||
154 | return $ scribeDate y m d | ||
155 | , try $ do | ||
156 | ds <- lookAhead $ length <$ (optional $ ($ ()) <$> sign) <*> some digitChar | ||
157 | let yDs = ds - 2 {- month-} - 2 {- day -} | ||
158 | when (yDs <= 0) $ | ||
159 | fail "Too few digits to interpret as concatenated date" | ||
160 | (Just -> y) <- optSigned . boundedNatural True $ 10^(pred yDs) <=..< 10^yDs | ||
161 | m <- monthNumber True | ||
162 | d <- dayNumber True | ||
163 | return $ scribeDate y m d | ||
164 | , monthName <$$> \m -> shiftBack (1 % Year) $ do | ||
165 | scribe (prio' Assign . flexDT.date.months) m | ||
166 | scribe (prio' Assign . flexDT.date.days) 1 | ||
167 | , weekdayName <$$> \w -> shiftBack (1 % Week) $ do | ||
168 | scribe (prio' Assign . weekDate._3) w | ||
169 | ] | ||
170 | where | ||
171 | withYear y | ||
172 | | Just y' <- y = (>>) $ scribe (prio' Assign . date.years) y' | ||
173 | | otherwise = shiftBack (1 % Year) | ||
174 | scribeDate y m d = withYear y $ do | ||
175 | scribe (prio' Assign . date.months) m | ||
176 | scribe (prio' Assign . flexDT.date.days) d | ||
177 | (<$$>) = flip (<$>) | ||
178 | monthName = choice $ zipWith (<$) [1..] [ string' "january" <|> string' "jan" | ||
179 | , string' "febuary" <|> string' "feb" | ||
180 | , string' "march" <|> string' "mar" | ||
181 | , string' "april" <|> string' "apr" | ||
182 | , string' "may" | ||
183 | , string' "june" <|> string' "jun" | ||
184 | , string' "july" <|> string' "jul" | ||
185 | , string' "august" <|> string' "aug" | ||
186 | , string' "september" <|> string' "sep" | ||
187 | , string' "october" <|> string' "oct" | ||
188 | , string' "november" <|> string' "nov" | ||
189 | , string' "december" <|> string' "dec" | ||
190 | ] | ||
191 | weekdayName = choice $ zipWith (<$) [1..] [ string' "monday" <|> string' "mon" | ||
192 | , string' "tuesday" <|> string' "tue" | ||
193 | , string' "wednesday" <|> string' "wed" | ||
194 | , string' "thursday" <|> string' "thu" | ||
195 | , string' "friday" <|> string' "fri" | ||
196 | , string' "saturday" <|> string' "sat" | ||
197 | , string' "sunday" <|> string' "sun" | ||
198 | ] | ||
199 | dayNumber p = boundedNatural p (1 <=..<= 31) | ||
200 | monthNumber p = boundedNatural p (1 <=..<= 12) | ||
201 | yearNumber = optSigned $ boundedNatural False (0 <=..< PosInf) | ||
133 | 202 | ||
134 | offsets :: forall s m. StringParser s m | 203 | offsets :: forall s m. StringParser s m |
135 | => Bool -- ^ Require sign on first offset? | 204 | => Bool -- ^ Require sign on first offset? |