summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <aethoago@141.li>2017-02-17 22:04:43 +0100
committerGregor Kleen <aethoago@141.li>2017-02-17 22:04:43 +0100
commit479d66dd0b3c2b6919e626b1c3c3fea9b0c9df8a (patch)
tree815b6f987c15cfb0cd3322a7900762418d46fd06
parentd84405d3e923f4677103143f8b7cc22c9adb6443 (diff)
downloadpostdelay-479d66dd0b3c2b6919e626b1c3c3fea9b0c9df8a.tar
postdelay-479d66dd0b3c2b6919e626b1c3c3fea9b0c9df8a.tar.gz
postdelay-479d66dd0b3c2b6919e626b1c3c3fea9b0c9df8a.tar.bz2
postdelay-479d66dd0b3c2b6919e626b1c3c3fea9b0c9df8a.tar.xz
postdelay-479d66dd0b3c2b6919e626b1c3c3fea9b0c9df8a.zip
Prioritised endomorphisms
-rw-r--r--lib/Postdelay/PrioMap.hs70
-rw-r--r--lib/Postdelay/TimeSpec.hs92
-rw-r--r--lib/Postdelay/TimeSpec/Utils.hs3
-rw-r--r--postdelay.cabal1
-rw-r--r--postdelay.nix14
5 files changed, 152 insertions, 28 deletions
diff --git a/lib/Postdelay/PrioMap.hs b/lib/Postdelay/PrioMap.hs
new file mode 100644
index 0000000..2b75984
--- /dev/null
+++ b/lib/Postdelay/PrioMap.hs
@@ -0,0 +1,70 @@
1{-# LANGUAGE TemplateHaskell, ViewPatterns, RankNTypes, GeneralizedNewtypeDeriving, DeriveTraversable, ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-}
2
3module Postdelay.PrioMap
4 ( PrioMap, prioMap, prioMap', _Endo
5 , prio, prios
6 , squash
7
8 , PrioEndo, prioEndo, prioEndo'
9 ) where
10
11import Data.IntMap.Strict (IntMap)
12import qualified Data.IntMap.Strict as IntMap
13
14import Control.Lens
15
16import Data.Foldable
17import Data.Semigroup
18
19
20makePrisms ''Endo
21
22newtype PrioMap p a = PrioMap (IntMap a)
23 deriving (Functor, Foldable, Traversable)
24makePrisms ''PrioMap
25
26instance Semigroup a => Semigroup (PrioMap p a) where
27 (PrioMap a) <> (PrioMap b) = PrioMap $ IntMap.unionWith (<>) a b
28
29instance Semigroup a => Monoid (PrioMap p a) where
30 mempty = PrioMap mempty
31 mappend = (<>)
32
33instance Enum p => FunctorWithIndex p (PrioMap p) where
34 imap f (PrioMap intMap) = PrioMap $ imap (f . toEnum) intMap
35
36instance Enum p => FoldableWithIndex p (PrioMap p) where
37 ifoldMap f (PrioMap intMap) = ifoldMap (f . toEnum) intMap
38
39instance Enum p => TraversableWithIndex p (PrioMap p) where
40 itraverse f (PrioMap intMap) = PrioMap <$> itraverse (f . toEnum) intMap
41
42
43prioMap :: (Enum p, Monoid a) => Iso' (PrioMap p a) a
44-- ^ `prioMap` squashes priority information into `0`
45prioMap = prioMap' $ toEnum 0
46
47prioMap' :: (Enum p, Monoid a) => p -> Iso' (PrioMap p a) a
48-- ^ `prioMap' p` squashes priority information into `p`
49prioMap' (fromEnum -> p) = _PrioMap . iso fold (IntMap.singleton p)
50
51prio :: Enum p => p -> Lens' (PrioMap p a) (Maybe a)
52prio (fromEnum -> p) = _PrioMap . at p
53
54squash :: Semigroup a => PrioMap p (PrioMap p a) -> PrioMap p a
55squash = unwrapMonoid . foldMap WrapMonoid
56
57prios :: forall f p arr a. (Bounded p, Enum p, Semigroup a, Applicative f, Indexable p arr) => arr (Maybe a) (f (Maybe a)) -> (PrioMap p a -> f (PrioMap p a))
58prios (indexed -> alter) pMap = foldr cons_f (pure $ PrioMap IntMap.empty) [minBound .. maxBound]
59 where
60 cons_f :: p -> f (PrioMap p a) -> f (PrioMap p a)
61 cons_f p x = (<>) <$> (maybe mempty (PrioMap . IntMap.singleton (fromEnum p)) <$> alter p (pMap ^. prio p)) <*> x
62
63
64type PrioEndo p a = PrioMap p (Endo a)
65
66prioEndo :: Enum p => Iso' (PrioEndo p a) (Endo a)
67prioEndo = prioMap
68
69prioEndo' :: Enum p => p -> Iso' (PrioEndo p a) (Endo a)
70prioEndo' = prioMap'
diff --git a/lib/Postdelay/TimeSpec.hs b/lib/Postdelay/TimeSpec.hs
index 4a32317..9361057 100644
--- a/lib/Postdelay/TimeSpec.hs
+++ b/lib/Postdelay/TimeSpec.hs
@@ -9,6 +9,7 @@ module Postdelay.TimeSpec
9 9
10import Postdelay.TimeSpec.Utils 10import Postdelay.TimeSpec.Utils
11import Postdelay.TimeSpec.Units 11import Postdelay.TimeSpec.Units
12import Postdelay.PrioMap
12 13
13import Text.Megaparsec 14import Text.Megaparsec
14 15
@@ -19,47 +20,67 @@ import Control.Exception (IOException)
19import Control.Monad.Catch hiding (try) 20import Control.Monad.Catch hiding (try)
20import Control.Monad.RWS hiding ((<>)) 21import Control.Monad.RWS hiding ((<>))
21 22
23import Data.Functor
22import Data.Bool 24import Data.Bool
23import Data.Semigroup hiding (option) 25import Data.Semigroup hiding (option)
24import Data.Monoid (Endo(..)) 26import Data.Monoid (Endo(..))
25import Data.Foldable 27import Data.Foldable
26import Data.VectorSpace 28import Data.VectorSpace
29import Data.Maybe
27 30
28import Data.Time 31import Data.Time as Time hiding (months)
32import Data.Time.Calendar.WeekDate
29import Data.Time.Lens 33import Data.Time.Lens
30import Data.Time.Zones 34import Data.Time.Zones
31 35
32 36
37data ModPrio = Offset | Assign | Shift | Default
38 deriving (Eq, Ord, Enum, Bounded, Show)
39
40
33seconds' :: Timeable t => Lens' t Time 41seconds' :: Timeable t => Lens' t Time
34seconds' = seconds . iso (% Second) (# Second) 42seconds' = seconds . iso (% Second) (# Second)
35 43
36utcOffset :: Iso' TimeZone Time 44utcOffset :: Iso' TimeZone Time
37utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute)) 45utcOffset = iso ((% Minute) . fromIntegral . timeZoneMinutes) (minutesToTimeZone . round . (# Minute))
38 46
39shiftBack :: MonadState LocalTime m => Time -> m a -> m a 47weekDate :: Dateable t => Lens' t (Integer, Int, Int)
40shiftBack by mod = join $ shiftBack' <$> get <*> mod <*> get 48weekDate = date . iso toWeekDate (\(y, w, d) -> fromWeekDate y w d)
41 where 49
42 shiftBack' prev ret new 50shiftBack :: (MonadReader LocalTime m, MonadWriter (PrioEndo ModPrio LocalTime) m)
43 | new < prev = ret <$ (flexDT.seconds' %= (^+^) by) 51 => Time -> PrioEndo ModPrio LocalTime -> m ()
44 | otherwise = pure ret 52shiftBack by mod@(view (prioEndo._Endo) -> modE) = do
53 tell mod
54
55 prev <- ask
56 new <- asks modE
57 case new <= prev of
58 True -> scribe (prio Shift) . Just . Endo $ flexDT.seconds' %~ ((^+^) by)
59 False -> return ()
60
61mod' :: ModPrio -> ASetter' LocalTime a -> a -> PrioEndo ModPrio LocalTime
62mod' priority setter val = mempty & prio priority .~ (Just . Endo $ set setter val)
63
64scribeMod :: MonadWriter (PrioEndo ModPrio LocalTime) m => ModPrio -> ASetter' LocalTime a -> a -> m ()
65scribeMod priority setter val = tell $ mod' priority setter val
45 66
46 67
47timeSpec :: forall s m. StringParser s m => m (Endo LocalTime) 68timeSpec :: forall s m. StringParser s m => m (Endo LocalTime)
48timeSpec = label "Relative time specification" $ 69timeSpec = label "Relative time specification" $ view prioEndo <$> choice
49 choice [ flip (<>) <$> lexeme specBase <*> option mempty (offsets True) 70 [ flip (<>) <$> lexeme specBase <*> option mempty (offsets True)
50 , lexeme (string' "now") *> offsets True 71 , lexeme (string' "now") *> offsets True
51 , offsets False 72 , offsets False
52 ] 73 ]
53 where 74 where
54 specBase = toEndo <$> mkGramSepBy spaces [ timeOfDay 75 specBase = toEndo <$> mkGramSepBy spaces [ timeOfDay
55 , dateSpec 76 , dateSpec
56 ] 77 ]
57 78
58 toEndo :: [RWS LocalTime () LocalTime a] -> Endo LocalTime 79 toEndo :: [RWS LocalTime (PrioEndo ModPrio LocalTime) () ()] -> PrioEndo ModPrio LocalTime
59 toEndo (sequence -> act) = Endo $ \t -> fst $ execRWS act t t 80 toEndo (sequence -> act) = mempty & prios .@~ (\i -> Just . Endo $ \t -> maybe t (($ t) . appEndo) . view (prio i) . snd $ execRWS act t ())
60 81
61timeOfDay, dateSpec :: StringParser s m => m (RWS LocalTime () LocalTime ()) 82timeOfDay, dateSpec :: StringParser s m => m (RWS LocalTime (PrioEndo ModPrio LocalTime) () ())
62timeOfDay = label "Time of day" $ shiftBack (1 % Day) . assign time <$> choice 83timeOfDay = label "Time of day" $ withShift <$> choice
63 [ TimeOfDay 0 0 0 <$ string' "midnight" 84 [ TimeOfDay 0 0 0 <$ string' "midnight"
64 , TimeOfDay 12 0 0 <$ string' "noon" 85 , TimeOfDay 12 0 0 <$ string' "noon"
65 , TimeOfDay 16 0 0 <$ string' "teatime" 86 , TimeOfDay 16 0 0 <$ string' "teatime"
@@ -75,22 +96,51 @@ timeOfDay = label "Time of day" $ shiftBack (1 % Day) . assign time <$> choice
75 spaceConsumer 96 spaceConsumer
76 amPm <- (0 <$ string' "am") <|> (12 <$ string' "pm") 97 amPm <- (0 <$ string' "am") <|> (12 <$ string' "pm")
77 return $ TimeOfDay (h + amPm) m s 98 return $ TimeOfDay (h + amPm) m s
99 , try $ do
100 h <- hour24 False
101 m <- option 0 $ char ':' *> minute False
102 s <- option 0 $ char ':' *> second False
103 return $ TimeOfDay h m s
78 ] 104 ]
79 where 105 where
80 hour12 pad = label "Modulus 12 hour" . fmap (flip mod 12) . boundedNatural pad $ 1 <=..<= 12 106 hour12 pad = label "Modulus 12 hour" . fmap (flip mod 12) . boundedNatural pad $ 1 <=..<= 12
81 hour24 pad = label "Modulus 24 hour" . boundedNatural pad $ 0 <=..< 24 107 hour24 pad = label "Modulus 24 hour" . boundedNatural pad $ 0 <=..< 24
82 minute pad = label "Minute" . boundedNatural pad $ 0 <=..< 60 108 minute pad = label "Minute" . boundedNatural pad $ 0 <=..< 60
83 second pad = label "Second" . boundedRational pad $ 0 <=..< 61 109 second pad = label "Second" . boundedRational pad $ 0 <=..< 61
110
111 withShift :: TimeOfDay -> RWS LocalTime (PrioEndo ModPrio LocalTime) () ()
112 withShift = shiftBack (1 % Day) . mod' Assign time
84 113
85dateSpec = label "Date" $ (date <~) <$> choice 114dateSpec = label "Date" $ choice
86 [ view date <$ string' "today" 115 [ (scribeMod Assign date =<< view date) <$ string' "today"
87 , views date succ <$ string' "tomorrow" 116 , (scribeMod Assign date =<< views date succ) <$ string' "tomorrow"
117 , do
118 string' "next"
119 spaces
120 choice
121 [ string' "day" $> do
122 scribeMod Assign (flexDT.date.days) =<< views (date.days) succ
123 scribeMod Default time midnight
124 , string' "week" $> do
125 scribeMod Assign (flexDT.date.days) =<< views (date.days) (+ 7)
126 scribeMod Assign (weekDate._3) 1
127 scribeMod Default time midnight
128 , string' "month" $> do
129 scribeMod Assign (flexDT.date.months) =<< views (date.months) succ
130 scribeMod Assign (date.days) 1
131 scribeMod Default time midnight
132 , string' "year" $> do
133 scribeMod Assign (flexDT.date.years) =<< views (date.years) succ
134 scribeMod Assign (date.months) 1
135 scribeMod Assign (date.days) 1
136 scribeMod Default time midnight
137 ]
88 ] 138 ]
89 139
90offsets :: forall s m. StringParser s m 140offsets :: forall s m. StringParser s m
91 => Bool -- ^ Require sign on first offset? 141 => Bool -- ^ Require sign on first offset?
92 -> m (Endo LocalTime) 142 -> m (PrioEndo ModPrio LocalTime)
93offsets reqSgn = fmap fold $ (:) <$> offset reqSgn <*> many (offset False) 143offsets reqSgn = fmap (foldMap . review $ prioEndo' Offset) $ (:) <$> offset reqSgn <*> many (offset False)
94 where 144 where
95 asOffset :: Time -> Endo LocalTime 145 asOffset :: Time -> Endo LocalTime
96 asOffset by = Endo $ flexDT.seconds' %~ (^+^ by) 146 asOffset by = Endo $ flexDT.seconds' %~ (^+^ by)
diff --git a/lib/Postdelay/TimeSpec/Utils.hs b/lib/Postdelay/TimeSpec/Utils.hs
index 628a1d9..0bce51a 100644
--- a/lib/Postdelay/TimeSpec/Utils.hs
+++ b/lib/Postdelay/TimeSpec/Utils.hs
@@ -35,6 +35,8 @@ import Text.Megaparsec
35import Text.Megaparsec.Prim (MonadParsec) 35import Text.Megaparsec.Prim (MonadParsec)
36import qualified Text.Megaparsec.Lexer as L 36import qualified Text.Megaparsec.Lexer as L
37 37
38import Debug.Trace
39
38 40
39type StringParser s m = (MonadParsec Dec s m, Token s ~ Char) 41type StringParser s m = (MonadParsec Dec s m, Token s ~ Char)
40 42
@@ -86,6 +88,7 @@ boundedNatural padded (I.intersection (0 <=..< PosInf) -> bounds) = do
86 | otherwise = int 88 | otherwise = int
87 89
88 digits :: n -> Int 90 digits :: n -> Int
91 digits 0 = 1
89 digits n = succ . fromJust $ findIndex (\(min, max) -> min <= n && n < max) [ (10^i, 10^(succ i)) | i <- ([0..] :: [Int]) ] 92 digits n = succ . fromJust $ findIndex (\(min, max) -> min <= n && n < max) [ (10^i, 10^(succ i)) | i <- ([0..] :: [Int]) ]
90 93
91boundedRational :: forall s m n. (Show n, RealFrac n, StringParser s m) 94boundedRational :: forall s m n. (Show n, RealFrac n, StringParser s m)
diff --git a/postdelay.cabal b/postdelay.cabal
index b184ce4..ad8f59e 100644
--- a/postdelay.cabal
+++ b/postdelay.cabal
@@ -39,6 +39,7 @@ library
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 , data-interval >=1.2 && <2
42 , containers >=0.5.7 && <1
42 hs-source-dirs: lib 43 hs-source-dirs: lib
43 default-language: Haskell2010 44 default-language: Haskell2010
44 45
diff --git a/postdelay.nix b/postdelay.nix
index 4c1dca6..d6fce32 100644
--- a/postdelay.nix
+++ b/postdelay.nix
@@ -1,7 +1,7 @@
1{ mkDerivation, base, case-insensitive, data-interval, exceptions 1{ mkDerivation, base, case-insensitive, containers, data-interval
2, hsemail, lens, lens-datetime, list-t, megaparsec, mime, mtl 2, exceptions, hsemail, lens, lens-datetime, list-t, megaparsec
3, old-time, parsec, stdenv, time, transformers, tz, units 3, mime, mtl, old-time, parsec, stdenv, time, transformers, tz
4, units-defs 4, units, units-defs
5}: 5}:
6mkDerivation { 6mkDerivation {
7 pname = "postdelay"; 7 pname = "postdelay";
@@ -10,9 +10,9 @@ mkDerivation {
10 isLibrary = true; 10 isLibrary = true;
11 isExecutable = true; 11 isExecutable = true;
12 libraryHaskellDepends = [ 12 libraryHaskellDepends = [
13 base case-insensitive data-interval exceptions hsemail lens 13 base case-insensitive containers data-interval exceptions hsemail
14 lens-datetime list-t megaparsec mime mtl old-time parsec time tz 14 lens lens-datetime list-t megaparsec mime mtl old-time parsec time
15 units units-defs 15 tz units units-defs
16 ]; 16 ];
17 executableHaskellDepends = [ base transformers ]; 17 executableHaskellDepends = [ base transformers ];
18 homepage = "https://git.yggdrasil.li/gkleen/pub/postdelay"; 18 homepage = "https://git.yggdrasil.li/gkleen/pub/postdelay";