diff options
| author | Gregor Kleen <aethoago@141.li> | 2017-02-15 19:04:57 +0100 |
|---|---|---|
| committer | Gregor Kleen <aethoago@141.li> | 2017-02-15 19:04:57 +0100 |
| commit | 127c1212d7704392363e3614f339627bf514cfcf (patch) | |
| tree | 10e9a0a1f48ec8aef518c3c33a6e34a7043d9738 | |
| parent | 5b09b096e38ed231b62df57736e87c989b481b5d (diff) | |
| download | postdelay-127c1212d7704392363e3614f339627bf514cfcf.tar postdelay-127c1212d7704392363e3614f339627bf514cfcf.tar.gz postdelay-127c1212d7704392363e3614f339627bf514cfcf.tar.bz2 postdelay-127c1212d7704392363e3614f339627bf514cfcf.tar.xz postdelay-127c1212d7704392363e3614f339627bf514cfcf.zip | |
Timezones
| -rw-r--r-- | lib/Postdelay/Scan.hs | 5 | ||||
| -rw-r--r-- | lib/Postdelay/TimeSpec.hs | 49 | ||||
| -rw-r--r-- | lib/Postdelay/TimeSpec/Units.hs | 4 | ||||
| -rw-r--r-- | lib/Postdelay/TimeSpec/Utils.hs | 3 |
4 files changed, 45 insertions, 16 deletions
diff --git a/lib/Postdelay/Scan.hs b/lib/Postdelay/Scan.hs index 888a237..0a265b4 100644 --- a/lib/Postdelay/Scan.hs +++ b/lib/Postdelay/Scan.hs | |||
| @@ -68,10 +68,9 @@ extractDelay (Message headers _) = do | |||
| 68 | zoneHeaders = runListT $ do | 68 | zoneHeaders = runListT $ do |
| 69 | (OptionalField field content) <- ListT $ return headers | 69 | (OptionalField field content) <- ListT $ return headers |
| 70 | guard $ CI.mk field == "X-Timezone" | 70 | guard $ CI.mk field == "X-Timezone" |
| 71 | Right r <- runParserT (spaceConsumer *> lexeme pTimeZone <* eof) field content | 71 | either throwM return =<< runParserT (spaceConsumer *> lexeme timeZone <* eof) field content |
| 72 | return r | ||
| 73 | parseDelay :: Field -> m (Endo LocalTime) | 72 | parseDelay :: Field -> m (Endo LocalTime) |
| 74 | parseDelay (OptionalField field content) = either throwM return =<< runParserT (spaceConsumer *> lexeme pTimeSpec <* eof) field content | 73 | parseDelay (OptionalField field content) = either throwM return =<< runParserT (spaceConsumer *> lexeme timeSpec <* eof) field content |
| 75 | 74 | ||
| 76 | localT :: Either TimeZone TZ -> Iso' UTCTime LocalTime | 75 | localT :: Either TimeZone TZ -> Iso' UTCTime LocalTime |
| 77 | 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 03baf85..fbbce6b 100644 --- a/lib/Postdelay/TimeSpec.hs +++ b/lib/Postdelay/TimeSpec.hs | |||
| @@ -1,8 +1,8 @@ | |||
| 1 | {-# LANGUAGE FlexibleContexts, ScopedTypeVariables, ViewPatterns, ConstraintKinds, TupleSections, RecordWildCards, TypeFamilies #-} | 1 | {-# LANGUAGE FlexibleContexts, ScopedTypeVariables, ViewPatterns, ConstraintKinds, TupleSections, RecordWildCards, TypeFamilies #-} |
| 2 | 2 | ||
| 3 | module Postdelay.TimeSpec | 3 | module Postdelay.TimeSpec |
| 4 | ( pTimeSpec | 4 | ( timeSpec |
| 5 | , pTimeZone | 5 | , timeZone |
| 6 | 6 | ||
| 7 | , spaceConsumer, lexeme | 7 | , spaceConsumer, lexeme |
| 8 | ) where | 8 | ) where |
| @@ -15,6 +15,8 @@ import Text.Megaparsec | |||
| 15 | import Control.Monad.IO.Class | 15 | 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) | ||
| 19 | import Control.Monad.Catch | ||
| 18 | 20 | ||
| 19 | import Data.Bool | 21 | import Data.Bool |
| 20 | import Data.Semigroup hiding (option) | 22 | import Data.Semigroup hiding (option) |
| @@ -30,22 +32,49 @@ import Data.Time.Zones | |||
| 30 | seconds' :: Timeable t => Lens' t Time | 32 | seconds' :: Timeable t => Lens' t Time |
| 31 | seconds' = seconds . iso (% Second) (# Second) | 33 | seconds' = seconds . iso (% Second) (# Second) |
| 32 | 34 | ||
| 35 | utcOffset :: Iso' TimeZone Time | ||
| 36 | utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute)) | ||
| 33 | 37 | ||
| 34 | pTimeSpec :: StringParser s m => m (Endo LocalTime) | 38 | |
| 35 | pTimeSpec = label "Relative time specification" $ | 39 | timeSpec :: StringParser s m => m (Endo LocalTime) |
| 36 | choice [ pOffsets False | 40 | timeSpec = label "Relative time specification" $ |
| 41 | choice [ offsets False | ||
| 37 | ] | 42 | ] |
| 38 | 43 | ||
| 39 | pOffsets :: forall s m. StringParser s m | 44 | offsets :: forall s m. StringParser s m |
| 40 | => Bool -- ^ Require sign on first offset? | 45 | => Bool -- ^ Require sign on first offset? |
| 41 | -> m (Endo LocalTime) | 46 | -> m (Endo LocalTime) |
| 42 | pOffsets (bool optSigned signed -> reqSgn) = fmap fold $ (:) <$> offset reqSgn <*> many (offset optSigned) | 47 | offsets (bool optSigned signed -> reqSgn) = fmap fold $ (:) <$> offset reqSgn <*> many (offset optSigned) |
| 43 | where | 48 | where |
| 44 | asOffset :: Time -> Endo LocalTime | 49 | asOffset :: Time -> Endo LocalTime |
| 45 | asOffset by = Endo $ flexDT.seconds' %~ (^+^ by) | 50 | asOffset by = Endo $ flexDT.seconds' %~ (^+^ by) |
| 46 | offset :: (m Time -> m Time) -> m (Endo LocalTime) | 51 | offset :: (m Time -> m Time) -> m (Endo LocalTime) |
| 47 | offset sgn = asOffset <$> lexeme (sgn timeLength) <?> "Time offset" | 52 | offset sgn = asOffset <$> lexeme (sgn timeLength) <?> "Time offset" |
| 48 | 53 | ||
| 49 | pTimeZone :: (StringParser s m, MonadIO m) => m (Either TimeZone TZ) | 54 | timeZone :: (StringParser s m, MonadIO m) => m (Either TimeZone TZ) |
| 50 | pTimeZone = label "Timezone" $ | 55 | timeZone = label "Timezone" $ (Left <$> numericTimezone) <|> (Right <$> namedTimezone) |
| 51 | empty | 56 | |
| 57 | numericTimezone :: StringParser s m => m TimeZone | ||
| 58 | numericTimezone = review utcOffset <$> (sign <*> ((^+^) <$> hour <*> minute)) <?> "Numeric timezone" | ||
| 59 | where | ||
| 60 | hour = (% Hour) <$> twoDigit | ||
| 61 | minute = (% Minute) <$> twoDigit | ||
| 62 | twoDigit = (\n1 n2 -> fromDigit n1 * 10 + fromDigit n2) <$> digitChar <*> digitChar | ||
| 63 | |||
| 64 | namedTimezone :: (StringParser s m, MonadIO m) => m TZ | ||
| 65 | namedTimezone = do | ||
| 66 | n <- ident | ||
| 67 | tz <- liftIO $ do | ||
| 68 | let | ||
| 69 | fbHandler :: IO a -> (IOException -> IO a) | ||
| 70 | fbHandler fb _ = fb | ||
| 71 | foldl (\fb a -> a `catch` fbHandler fb) (return Nothing) | ||
| 72 | [ Just <$> loadSystemTZ n | ||
| 73 | , Just <$> loadTZFromDB n | ||
| 74 | ] | ||
| 75 | case tz of | ||
| 76 | Nothing -> fail $ "Could not resolve timezone: " ++ show n | ||
| 77 | (Just tz) -> return tz | ||
| 78 | where | ||
| 79 | asciiAlphaNum = oneOf $ ['0'..'9'] ++ ['a'..'z'] ++ ['A'..'Z'] | ||
| 80 | ident = (++) <$> some asciiAlphaNum <*> option [] ((:) <$> oneOf "_-/.+" <*> ident) <?> "Named timezone identifier" | ||
diff --git a/lib/Postdelay/TimeSpec/Units.hs b/lib/Postdelay/TimeSpec/Units.hs index 0062460..a094ea3 100644 --- a/lib/Postdelay/TimeSpec/Units.hs +++ b/lib/Postdelay/TimeSpec/Units.hs | |||
| @@ -62,10 +62,8 @@ rational :: forall s m n. (StringParser s m, Fractional n, Num n) => m n | |||
| 62 | rational = combine <$> some digitChar <*> option [] (char '.' *> many digitChar) <?> "Decimal number" | 62 | rational = combine <$> some digitChar <*> option [] (char '.' *> many digitChar) <?> "Decimal number" |
| 63 | where | 63 | where |
| 64 | combine :: [Char] -> [Char] -> n | 64 | combine :: [Char] -> [Char] -> n |
| 65 | combine (map asN -> whole) (map asN -> fractional) | 65 | combine (map fromDigit -> whole) (map fromDigit -> fractional) |
| 66 | = foldl' (\i l -> i * 10 + l) 0 whole + (foldr' (\h t -> h + t / 10) 0 fractional) / 10 | 66 | = foldl' (\i l -> i * 10 + l) 0 whole + (foldr' (\h t -> h + t / 10) 0 fractional) / 10 |
| 67 | asN :: Char -> n | ||
| 68 | asN c = fromIntegral $ fromEnum c - fromEnum '0' | ||
| 69 | 67 | ||
| 70 | timeUnit :: StringParser s m => m Time | 68 | timeUnit :: StringParser s m => m Time |
| 71 | timeUnit = label "Unit of time" . choice $ | 69 | timeUnit = label "Unit of time" . choice $ |
diff --git a/lib/Postdelay/TimeSpec/Utils.hs b/lib/Postdelay/TimeSpec/Utils.hs index 85ac299..83a271d 100644 --- a/lib/Postdelay/TimeSpec/Utils.hs +++ b/lib/Postdelay/TimeSpec/Utils.hs | |||
| @@ -35,3 +35,6 @@ sign :: (StringParser s m, AdditiveGroup n) => m (n -> n) | |||
| 35 | sign = label "sign" $ choice [ char '+' $> id | 35 | sign = label "sign" $ choice [ char '+' $> id |
| 36 | , char '-' $> negateV | 36 | , char '-' $> negateV |
| 37 | ] | 37 | ] |
| 38 | |||
| 39 | fromDigit :: Num n => Char -> n | ||
| 40 | fromDigit c = fromIntegral $ fromEnum c - fromEnum '0' | ||
