diff options
-rw-r--r-- | lib/Postdelay/TimeSpec.hs | 7 | ||||
-rw-r--r-- | lib/Postdelay/TimeSpec/Units.hs | 9 | ||||
-rw-r--r-- | lib/Postdelay/TimeSpec/Utils.hs | 69 | ||||
-rw-r--r-- | postdelay.cabal | 1 | ||||
-rw-r--r-- | postdelay.nix | 12 |
5 files changed, 83 insertions, 15 deletions
diff --git a/lib/Postdelay/TimeSpec.hs b/lib/Postdelay/TimeSpec.hs index 384de4b..edd70c1 100644 --- a/lib/Postdelay/TimeSpec.hs +++ b/lib/Postdelay/TimeSpec.hs | |||
@@ -56,13 +56,18 @@ timeSpec = label "Relative time specification" $ | |||
56 | ] | 56 | ] |
57 | 57 | ||
58 | toEndo :: [RWS LocalTime () LocalTime a] -> Endo LocalTime | 58 | toEndo :: [RWS LocalTime () LocalTime a] -> Endo LocalTime |
59 | toEndo acts = Endo $ \t -> fst $ execRWS (sequence acts) t t | 59 | toEndo (sequence -> act) = Endo $ \t -> fst $ execRWS act t t |
60 | 60 | ||
61 | timeOfDay, dateSpec :: StringParser s m => m (RWS LocalTime () LocalTime ()) | 61 | timeOfDay, dateSpec :: StringParser s m => m (RWS LocalTime () LocalTime ()) |
62 | timeOfDay = label "Time of day" $ shiftBack (1 % Day) . assign time <$> choice | 62 | timeOfDay = label "Time of day" $ shiftBack (1 % Day) . assign time <$> choice |
63 | [ TimeOfDay 0 0 0 <$ string' "midnight" | 63 | [ TimeOfDay 0 0 0 <$ string' "midnight" |
64 | , TimeOfDay 12 0 0 <$ string' "noon" | 64 | , TimeOfDay 12 0 0 <$ string' "noon" |
65 | , TimeOfDay 16 0 0 <$ string' "teatime" | 65 | , TimeOfDay 16 0 0 <$ string' "teatime" |
66 | , try $ do | ||
67 | h <- boundedNatural True $ 0 <=..<= 24 | ||
68 | m <- boundedNatural True $ 0 <=..<= 59 | ||
69 | s <- option 0 $ boundedRational True $ 0 <=..< 61 | ||
70 | return $ TimeOfDay h m s | ||
66 | ] | 71 | ] |
67 | dateSpec = label "Date" $ (date <~) <$> choice | 72 | dateSpec = label "Date" $ (date <~) <$> choice |
68 | [ view date <$ string' "today" | 73 | [ view date <$ string' "today" |
diff --git a/lib/Postdelay/TimeSpec/Units.hs b/lib/Postdelay/TimeSpec/Units.hs index a094ea3..4874ce9 100644 --- a/lib/Postdelay/TimeSpec/Units.hs +++ b/lib/Postdelay/TimeSpec/Units.hs | |||
@@ -56,14 +56,7 @@ instance HasResolution p => VectorSpace (Fixed p) where | |||
56 | 56 | ||
57 | 57 | ||
58 | timeLength :: StringParser s m => m Time | 58 | timeLength :: StringParser s m => m Time |
59 | timeLength = (*^) <$> lexeme rational <*> timeUnit <?> "Length of time" | 59 | timeLength = (*^) <$> lexeme (boundedRational False $ 0 <=..< PosInf) <*> timeUnit <?> "Length of time" |
60 | |||
61 | 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" | ||
63 | where | ||
64 | combine :: [Char] -> [Char] -> n | ||
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 | ||
67 | 60 | ||
68 | timeUnit :: StringParser s m => m Time | 61 | timeUnit :: StringParser s m => m Time |
69 | timeUnit = label "Unit of time" . choice $ | 62 | timeUnit = label "Unit of time" . choice $ |
diff --git a/lib/Postdelay/TimeSpec/Utils.hs b/lib/Postdelay/TimeSpec/Utils.hs index 54b85f7..c10fc4b 100644 --- a/lib/Postdelay/TimeSpec/Utils.hs +++ b/lib/Postdelay/TimeSpec/Utils.hs | |||
@@ -1,6 +1,17 @@ | |||
1 | {-# LANGUAGE RankNTypes, ConstraintKinds, TypeFamilies, FlexibleContexts, ScopedTypeVariables, ViewPatterns, TupleSections #-} | 1 | {-# LANGUAGE RankNTypes, ConstraintKinds, TypeFamilies, FlexibleContexts, ScopedTypeVariables, ViewPatterns, TupleSections #-} |
2 | 2 | ||
3 | module Postdelay.TimeSpec.Utils where | 3 | module Postdelay.TimeSpec.Utils |
4 | ( StringParser | ||
5 | , spaceConsumer, spaces | ||
6 | , lexeme | ||
7 | , signed, optSigned | ||
8 | , sign | ||
9 | , boundedNatural | ||
10 | , boundedRational | ||
11 | , module Data.Interval | ||
12 | , fromDigit | ||
13 | , mkGramSepBy | ||
14 | ) where | ||
4 | 15 | ||
5 | import Control.Applicative | 16 | import Control.Applicative |
6 | import Control.Monad | 17 | import Control.Monad |
@@ -10,8 +21,13 @@ import Data.Time | |||
10 | import Data.Time.Lens | 21 | import Data.Time.Lens |
11 | import Data.Time.Zones | 22 | import Data.Time.Zones |
12 | 23 | ||
24 | import Data.Bool | ||
25 | import Data.Foldable | ||
13 | import Data.Functor | 26 | import Data.Functor |
27 | import Data.Function | ||
14 | import Data.AdditiveGroup | 28 | import Data.AdditiveGroup |
29 | import Data.Interval (Interval, Extended(..), (<=..<=), (<=..<), (<..<=), (<..<), interval) | ||
30 | import qualified Data.Interval as I | ||
15 | 31 | ||
16 | import Text.Megaparsec | 32 | import Text.Megaparsec |
17 | import Text.Megaparsec.Prim (MonadParsec) | 33 | import Text.Megaparsec.Prim (MonadParsec) |
@@ -37,6 +53,57 @@ sign = label "sign" $ choice [ char '+' $> id | |||
37 | , char '-' $> negateV | 53 | , char '-' $> negateV |
38 | ] | 54 | ] |
39 | 55 | ||
56 | boundedNatural :: forall s n m. (Show n, Real n, StringParser s m) | ||
57 | => Bool -- ^ Require number to be padded with zeroes? | ||
58 | -> Interval n -> m n | ||
59 | boundedNatural padded (I.intersection (0 <=..< PosInf) -> bounds) = do | ||
60 | n <- foldl' (\i l -> i * 10 + l) 0 <$> digitN (fromDigit <$> digitChar) <?> "Natural number cotained in: " ++ show bounds | ||
61 | when (not $ n `I.member` bounds) $ fail "Natural number out of bounds" | ||
62 | return n | ||
63 | where | ||
64 | digitN :: m n -> m [n] | ||
65 | digitN p | ||
66 | | PosInf <- maxDigits | ||
67 | , Finite min <- minDigits = (++) <$> count min p <*> many p | ||
68 | | Finite max <- maxDigits | ||
69 | , Finite min <- minDigits | ||
70 | , not padded = count' min max p | ||
71 | | Finite max <- maxDigits | ||
72 | , Finite _ <- minDigits | ||
73 | , padded = count max p | ||
74 | | otherwise = error "boundedNatural in undefined state" | ||
75 | |||
76 | minDigits, maxDigits :: Extended Int | ||
77 | (minDigits, maxDigits) = ( fmap digits . I.lowerBound $ close bounds | ||
78 | , fmap digits . I.upperBound $ close bounds | ||
79 | ) | ||
80 | where | ||
81 | close int | ||
82 | | (Finite min, False) <- I.lowerBound' int = close $ interval (Finite $ min + 1, True) (I.upperBound' int) | ||
83 | | (Finite max, False) <- I.upperBound' int = close $ interval (I.lowerBound' int) (Finite $ max - 1, True) | ||
84 | | otherwise = int | ||
85 | |||
86 | digits :: n -> Int | ||
87 | digits = ceiling . (logBase 10 :: Double -> Double) . realToFrac . abs | ||
88 | |||
89 | boundedRational :: forall s m n. (Show n, RealFrac n, StringParser s m) | ||
90 | => Bool -- ^ Require number to be padded with zeroes | ||
91 | -> Interval n -> m n | ||
92 | boundedRational padded (I.intersection (0 <=..< PosInf) -> bounds) | ||
93 | = (+) <$> boundedNatural padded wholeBounds <*> fractional <?> "Nonnegative real contained in: " ++ show bounds | ||
94 | where | ||
95 | fractional :: m n | ||
96 | fractional = reqFractional $ char '.' $> (/ 10) . foldr' (\h t -> h + t / 10) 0 <*> some (fromDigit <$> digitChar) | ||
97 | |||
98 | reqFractional | ||
99 | | contained = option 0 | ||
100 | | otherwise = id | ||
101 | where (_, contained) = I.lowerBound' bounds | ||
102 | wholeBounds | ||
103 | | (Finite max, False) <- I.upperBound' bounds | ||
104 | , max == (fromInteger $ round max) = interval (I.lowerBound' bounds) (Finite $ max - 1, True) | ||
105 | | otherwise = bounds | ||
106 | |||
40 | fromDigit :: Num n => Char -> n | 107 | fromDigit :: Num n => Char -> n |
41 | fromDigit c = fromIntegral $ fromEnum c - fromEnum '0' | 108 | fromDigit c = fromIntegral $ fromEnum c - fromEnum '0' |
42 | 109 | ||
diff --git a/postdelay.cabal b/postdelay.cabal index 6d4323a..b184ce4 100644 --- a/postdelay.cabal +++ b/postdelay.cabal | |||
@@ -38,6 +38,7 @@ library | |||
38 | , exceptions >=0.8 && <1 | 38 | , exceptions >=0.8 && <1 |
39 | , lens >=4.15 && <5 | 39 | , lens >=4.15 && <5 |
40 | , lens-datetime >=0.3 && <1 | 40 | , lens-datetime >=0.3 && <1 |
41 | , data-interval >=1.2 && <2 | ||
41 | hs-source-dirs: lib | 42 | hs-source-dirs: lib |
42 | default-language: Haskell2010 | 43 | default-language: Haskell2010 |
43 | 44 | ||
diff --git a/postdelay.nix b/postdelay.nix index 938557f..4c1dca6 100644 --- a/postdelay.nix +++ b/postdelay.nix | |||
@@ -1,6 +1,7 @@ | |||
1 | { mkDerivation, base, case-insensitive, exceptions, hsemail, lens | 1 | { mkDerivation, base, case-insensitive, data-interval, exceptions |
2 | , lens-datetime, list-t, megaparsec, mime, mtl, old-time, parsec | 2 | , hsemail, lens, lens-datetime, list-t, megaparsec, mime, mtl |
3 | , stdenv, time, transformers, tz, units, units-defs | 3 | , old-time, parsec, stdenv, time, transformers, tz, units |
4 | , units-defs | ||
4 | }: | 5 | }: |
5 | mkDerivation { | 6 | mkDerivation { |
6 | pname = "postdelay"; | 7 | pname = "postdelay"; |
@@ -9,8 +10,9 @@ mkDerivation { | |||
9 | isLibrary = true; | 10 | isLibrary = true; |
10 | isExecutable = true; | 11 | isExecutable = true; |
11 | libraryHaskellDepends = [ | 12 | libraryHaskellDepends = [ |
12 | base case-insensitive exceptions hsemail lens lens-datetime list-t | 13 | base case-insensitive data-interval exceptions hsemail lens |
13 | megaparsec mime mtl old-time parsec time tz units units-defs | 14 | lens-datetime list-t megaparsec mime mtl old-time parsec time tz |
15 | units units-defs | ||
14 | ]; | 16 | ]; |
15 | executableHaskellDepends = [ base transformers ]; | 17 | executableHaskellDepends = [ base transformers ]; |
16 | homepage = "https://git.yggdrasil.li/gkleen/pub/postdelay"; | 18 | homepage = "https://git.yggdrasil.li/gkleen/pub/postdelay"; |