diff options
author | Gregor Kleen <aethoago@141.li> | 2017-02-15 23:44:38 +0100 |
---|---|---|
committer | Gregor Kleen <aethoago@141.li> | 2017-02-15 23:44:38 +0100 |
commit | 6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8 (patch) | |
tree | ba65997b88262eedbc2f1f61f5acb3ce2f895747 /lib/Postdelay | |
parent | 0503ba7038a78094363a29408aee4ad6ee4cfb13 (diff) | |
download | postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar.gz postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar.bz2 postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.tar.xz postdelay-6cab5d804dd2f5a5bcaa74ebad2347c9581a06b8.zip |
Refined framework
Diffstat (limited to 'lib/Postdelay')
-rw-r--r-- | lib/Postdelay/Scan.hs | 2 | ||||
-rw-r--r-- | lib/Postdelay/TimeSpec.hs | 26 | ||||
-rw-r--r-- | lib/Postdelay/TimeSpec/Utils.hs | 22 |
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 | ||
75 | localT :: Either TimeZone TZ -> Iso' UTCTime LocalTime | 75 | localT :: Either TimeZone TZ -> Iso' UTCTime LocalTime |
76 | localT (Left tz) = iso (utcToLocalTime tz) (localTimeToUTC tz) | 76 | localT (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 | |||
16 | import Control.Applicative | 16 | import Control.Applicative |
17 | import Control.Lens hiding ((#)) | 17 | import Control.Lens hiding ((#)) |
18 | import Control.Exception (IOException) | 18 | import Control.Exception (IOException) |
19 | import Control.Monad.Catch | 19 | import Control.Monad.Catch hiding (try) |
20 | import Control.Monad.RWS hiding ((<>)) | ||
20 | 21 | ||
21 | import Data.Bool | 22 | import Data.Bool |
22 | import Data.Semigroup hiding (option) | 23 | import Data.Semigroup hiding (option) |
@@ -36,11 +37,30 @@ utcOffset :: Iso' TimeZone Time | |||
36 | utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute)) | 37 | utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute)) |
37 | 38 | ||
38 | 39 | ||
39 | timeSpec :: StringParser s m => m (Endo LocalTime) | 40 | timeSpec :: forall s m. StringParser s m => m (Endo LocalTime) |
40 | timeSpec = label "Relative time specification" $ | 41 | timeSpec = 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 | |||
54 | timeOfDay, absDate :: StringParser s m => m (RWS LocalTime () LocalTime ()) | ||
55 | timeOfDay = 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 | ] | ||
60 | absDate = label "Date" . (fmap . (=<<) . assign $ date) $ choice | ||
61 | [ view date <$ string' "today" | ||
62 | , views date succ <$ string' "tomorrow" | ||
63 | ] | ||
44 | 64 | ||
45 | offsets :: forall s m. StringParser s m | 65 | offsets :: 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 | ||
3 | module Postdelay.TimeSpec.Utils where | 3 | module Postdelay.TimeSpec.Utils where |
4 | 4 | ||
@@ -21,8 +21,9 @@ import qualified Text.Megaparsec.Lexer as L | |||
21 | type StringParser s m = (MonadParsec Dec s m, Token s ~ Char) | 21 | type StringParser s m = (MonadParsec Dec s m, Token s ~ Char) |
22 | 22 | ||
23 | 23 | ||
24 | spaceConsumer :: StringParser s m => m () | 24 | spaceConsumer, spaces :: StringParser s m => m () |
25 | spaceConsumer = L.space (void spaceChar) empty empty | 25 | spaceConsumer = L.space (void spaceChar) empty empty |
26 | spaces = void $ lexeme spaceChar | ||
26 | 27 | ||
27 | lexeme :: StringParser s m => m a -> m a | 28 | lexeme :: StringParser s m => m a -> m a |
28 | lexeme = L.lexeme spaceConsumer | 29 | lexeme = L.lexeme spaceConsumer |
@@ -38,3 +39,20 @@ sign = label "sign" $ choice [ char '+' $> id | |||
38 | 39 | ||
39 | fromDigit :: Num n => Char -> n | 40 | fromDigit :: Num n => Char -> n |
40 | fromDigit c = fromIntegral $ fromEnum c - fromEnum '0' | 41 | fromDigit c = fromIntegral $ fromEnum c - fromEnum '0' |
42 | |||
43 | mkGramSepBy :: MonadParsec e s m => m a -> [m b] -> m [b] | ||
44 | mkGramSepBy 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) | ||