summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <aethoago@141.li>2017-02-15 23:44:38 +0100
committerGregor Kleen <aethoago@141.li>2017-02-15 23:44:38 +0100
commit6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8 (patch)
treeba65997b88262eedbc2f1f61f5acb3ce2f895747
parent0503ba7038a78094363a29408aee4ad6ee4cfb13 (diff)
downloadpostdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar
postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar.gz
postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar.bz2
postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar.xz
postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.zip
Refined framework
-rw-r--r--lib/Postdelay/Scan.hs2
-rw-r--r--lib/Postdelay/TimeSpec.hs26
-rw-r--r--lib/Postdelay/TimeSpec/Utils.hs22
3 files changed, 44 insertions, 6 deletions
diff --git a/lib/Postdelay/Scan.hs b/lib/Postdelay/Scan.hs
index 0a265b4..7f80818 100644
--- a/lib/Postdelay/Scan.hs
+++ b/lib/Postdelay/Scan.hs
@@ -70,7 +70,7 @@ extractDelay (Message headers _) = do
70 guard $ CI.mk field == "X-Timezone" 70 guard $ CI.mk field == "X-Timezone"
71 either throwM return =<< runParserT (spaceConsumer *> lexeme timeZone <* eof) field content 71 either throwM return =<< runParserT (spaceConsumer *> lexeme timeZone <* eof) field content
72 parseDelay :: Field -> m (Endo LocalTime) 72 parseDelay :: Field -> m (Endo LocalTime)
73 parseDelay (OptionalField field content) = either throwM return =<< runParserT (spaceConsumer *> lexeme timeSpec <* eof) field content 73 parseDelay (OptionalField field content) = either throwM return =<< runParserT (spaceConsumer *> timeSpec <* eof) field content
74 74
75localT :: Either TimeZone TZ -> Iso' UTCTime LocalTime 75localT :: Either TimeZone TZ -> Iso' UTCTime LocalTime
76localT (Left tz) = iso (utcToLocalTime tz) (localTimeToUTC tz) 76localT (Left tz) = iso (utcToLocalTime tz) (localTimeToUTC tz)
diff --git a/lib/Postdelay/TimeSpec.hs b/lib/Postdelay/TimeSpec.hs
index a72f87e..8244885 100644
--- a/lib/Postdelay/TimeSpec.hs
+++ b/lib/Postdelay/TimeSpec.hs
@@ -16,7 +16,8 @@ import Control.Monad.IO.Class
16import Control.Applicative 16import Control.Applicative
17import Control.Lens hiding ((#)) 17import Control.Lens hiding ((#))
18import Control.Exception (IOException) 18import Control.Exception (IOException)
19import Control.Monad.Catch 19import Control.Monad.Catch hiding (try)
20import Control.Monad.RWS hiding ((<>))
20 21
21import Data.Bool 22import Data.Bool
22import Data.Semigroup hiding (option) 23import Data.Semigroup hiding (option)
@@ -36,11 +37,30 @@ utcOffset :: Iso' TimeZone Time
36utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute)) 37utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute))
37 38
38 39
39timeSpec :: StringParser s m => m (Endo LocalTime) 40timeSpec :: forall s m. StringParser s m => m (Endo LocalTime)
40timeSpec = label "Relative time specification" $ 41timeSpec = label "Relative time specification" $
41 choice [ lexeme (string' "now") *> offsets True 42 choice [ flip (<>) <$> lexeme specBase <*> option mempty (offsets True)
43 , lexeme (string' "now") *> offsets True
42 , offsets False 44 , offsets False
43 ] 45 ]
46 where
47 specBase = foldMap toEndo <$> mkGramSepBy spaces [ absDate
48 , timeOfDay
49 ]
50
51 toEndo :: RWS LocalTime () LocalTime a -> Endo LocalTime
52 toEndo act = Endo $ \t -> fst $ execRWS act t t
53
54timeOfDay, absDate :: StringParser s m => m (RWS LocalTime () LocalTime ())
55timeOfDay = label "Time of day" $ assign time <$> choice
56 [ TimeOfDay 0 0 0 <$ string' "midnight"
57 , TimeOfDay 12 0 0 <$ string' "noon"
58 , TimeOfDay 16 0 0 <$ string' "teatime"
59 ]
60absDate = label "Date" . (fmap . (=<<) . assign $ date) $ choice
61 [ view date <$ string' "today"
62 , views date succ <$ string' "tomorrow"
63 ]
44 64
45offsets :: forall s m. StringParser s m 65offsets :: forall s m. StringParser s m
46 => Bool -- ^ Require sign on first offset? 66 => Bool -- ^ Require sign on first offset?
diff --git a/lib/Postdelay/TimeSpec/Utils.hs b/lib/Postdelay/TimeSpec/Utils.hs
index 83a271d..54b85f7 100644
--- a/lib/Postdelay/TimeSpec/Utils.hs
+++ b/lib/Postdelay/TimeSpec/Utils.hs
@@ -1,4 +1,4 @@
1{-# LANGUAGE RankNTypes, ConstraintKinds, TypeFamilies, FlexibleContexts, ScopedTypeVariables, ViewPatterns #-} 1{-# LANGUAGE RankNTypes, ConstraintKinds, TypeFamilies, FlexibleContexts, ScopedTypeVariables, ViewPatterns, TupleSections #-}
2 2
3module Postdelay.TimeSpec.Utils where 3module Postdelay.TimeSpec.Utils where
4 4
@@ -21,8 +21,9 @@ import qualified Text.Megaparsec.Lexer as L
21type StringParser s m = (MonadParsec Dec s m, Token s ~ Char) 21type StringParser s m = (MonadParsec Dec s m, Token s ~ Char)
22 22
23 23
24spaceConsumer :: StringParser s m => m () 24spaceConsumer, spaces :: StringParser s m => m ()
25spaceConsumer = L.space (void spaceChar) empty empty 25spaceConsumer = L.space (void spaceChar) empty empty
26spaces = void $ lexeme spaceChar
26 27
27lexeme :: StringParser s m => m a -> m a 28lexeme :: StringParser s m => m a -> m a
28lexeme = L.lexeme spaceConsumer 29lexeme = L.lexeme spaceConsumer
@@ -38,3 +39,20 @@ sign = label "sign" $ choice [ char '+' $> id
38 39
39fromDigit :: Num n => Char -> n 40fromDigit :: Num n => Char -> n
40fromDigit c = fromIntegral $ fromEnum c - fromEnum '0' 41fromDigit c = fromIntegral $ fromEnum c - fromEnum '0'
42
43mkGramSepBy :: MonadParsec e s m => m a -> [m b] -> m [b]
44mkGramSepBy sep ps = map snd <$> mkGramSepBy' sep (zip [0..] ps)
45 where
46 mkGramSepBy' _ [] = empty
47 mkGramSepBy' _ [(n, x)] = pure . (n, ) <$> x
48 mkGramSepBy' sep ps = do
49 head@(n, _) <- choice $ map (\(n, p) -> (n, ) <$> p) ps
50 let ps' = filter (\(i, _) -> i /= n) ps
51 tail <- option [] . try $ sep *> mkGramSepBy' sep ps'
52 return $ insert head tail
53
54 insert :: forall a. (Integer, a) -> [(Integer, a)] -> [(Integer, a)]
55 insert x@(fst -> a) [] = [x]
56 insert x@(fst -> a) (y@(fst -> b):ds)
57 | a <= b = x:y:ds
58 | otherwise = y:(insert x ds)