summaryrefslogtreecommitdiff
path: root/src/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Main.hs')
-rw-r--r--src/Main.hs62
1 files changed, 58 insertions, 4 deletions
diff --git a/src/Main.hs b/src/Main.hs
index 86c8771..4429853 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -1,4 +1,4 @@
1{-# LANGUAGE FlexibleContexts, ViewPatterns, OverloadedStrings #-} 1{-# LANGUAGE FlexibleContexts, ViewPatterns, OverloadedStrings, TupleSections #-}
2 2
3import Data.PQueue.Prio.Max (MaxPQueue) 3import Data.PQueue.Prio.Max (MaxPQueue)
4import qualified Data.PQueue.Prio.Max as MaxPQueue 4import qualified Data.PQueue.Prio.Max as MaxPQueue
@@ -9,8 +9,11 @@ import qualified Data.Sequence as Seq
9import Data.Text (Text) 9import Data.Text (Text)
10import qualified Data.Text as Text 10import qualified Data.Text as Text
11 11
12import Data.Set (Set)
13import qualified Data.Set as Set
14
12import Data.Default.Class 15import Data.Default.Class
13import Data.Maybe (fromMaybe) 16import Data.Maybe (fromMaybe, isNothing, fromJust)
14 17
15import System.Environment.XDG.BaseDir (getUserCacheFile) 18import System.Environment.XDG.BaseDir (getUserCacheFile)
16import System.Environment (getProgName) 19import System.Environment (getProgName)
@@ -54,7 +57,7 @@ runCli = do
54 57
55 Quit -> liftIO exitSuccess 58 Quit -> liftIO exitSuccess
56 59
57 Dump -> get >>= outputStrLn . show 60 Dump -> gets ctxSequence >>= mapM_ (outputStrLn . showAssoc) . MaxPQueue.toDescList
58 ShowTip -> do 61 ShowTip -> do
59 tip <- fmap snd <$> gets (MaxPQueue.getMax . ctxSequence) 62 tip <- fmap snd <$> gets (MaxPQueue.getMax . ctxSequence)
60 case tip of 63 case tip of
@@ -63,6 +66,57 @@ runCli = do
63 ShowHistory ns -> do 66 ShowHistory ns -> do
64 let sel = maybe id takeR ns 67 let sel = maybe id takeR ns
65 mapM_ (outputStrLn . show) =<< sel <$> gets ctxHistory 68 mapM_ (outputStrLn . show) =<< sel <$> gets ctxHistory
66 PerformAlt alt comment -> apply' alt comment 69 PerformAlt alt comment -> apply alt comment
67 _ -> undefined 70 _ -> undefined
68 runCli 71 runCli
72
73showAssoc :: (SequenceValue, Entity) -> String
74showAssoc (val, entity) = show val <> "\t" <> (Text.unpack $ showEntity entity)
75
76
77apply :: SequenceM m => Alteration -> Comment -> InputT m ()
78apply alteration comment = alter alteration >> modify (\ctx -> ctx { ctxHistory = ctxHistory ctx |> (alteration, comment) })
79
80alter :: SequenceM m => Alteration -> InputT m ()
81alter (Modify entity ((+) -> mod)) = alterMatching entity mod
82alter (Override entity (const -> mod)) = alterMatching entity mod
83alter (Rename old new) = do
84 [(k, _)] <- filter (\(_, v) -> v == old) <$> gets (MaxPQueue.assocsU . ctxSequence)
85 alter (Drop old)
86 alter (Insert new k)
87alter (Drop entity) = do
88 (matching, notMatching) <- MaxPQueue.partition (== entity) <$> gets ctxSequence
89 modify $ \ctx -> ctx { ctxSequence = notMatching }
90 when (MaxPQueue.null matching) warnEmpty
91alter (Insert entity val) = do
92 modify $ \ctx -> ctx { ctxSequence = MaxPQueue.insert val entity $ ctxSequence ctx }
93 introduceNumbering entity
94
95
96alterMatching :: SequenceM m => Entity -> (SequenceValue -> SequenceValue) -> InputT m ()
97alterMatching entity mod = do
98 (matching, notMatching) <- MaxPQueue.partition (== entity) <$> gets ctxSequence
99 modify $ \ctx -> ctx { ctxSequence = notMatching `MaxPQueue.union` MaxPQueue.mapKeys mod matching }
100 when (MaxPQueue.null matching) warnEmpty
101
102introduceNumbering :: SequenceM m => Entity -> InputT m ()
103introduceNumbering entity = do
104 let
105 matches (Entity name _) (Entity name' _) = name == name'
106 (matching, notMatching) <- MaxPQueue.partition (matches entity) <$> gets ctxSequence
107 if MaxPQueue.size matching <= 1
108 then return ()
109 else do
110 let
111 (matching', notMatching') = MaxPQueue.partition (\(Entity _ n) -> isNothing n) matching
112 maxN = MaxPQueue.foldrU (\(Entity _ n) -> max n) (Just 0) notMatching'
113 modify $ \ctx -> ctx { ctxSequence = snd $ MaxPQueue.foldrWithKey accum (fromJust maxN, MaxPQueue.union notMatching notMatching') matching' }
114 if MaxPQueue.null notMatching'
115 then outputStrLn $ "Had to introduce a numbering scheme to differentiate multiple entities called »" <> (Text.unpack $ showEntity entity) <> "«"
116 else outputStrLn $ "Inserted new entity called »" <> (Text.unpack $ showEntity entity) <> "« into existing numbering scheme"
117 where
118 accum key (Entity val _) (n, queue) = (succ n, MaxPQueue.insert key (Entity val $ Just (succ n)) queue)
119
120warnEmpty :: MonadIO m => InputT m ()
121warnEmpty = outputStrLn "Selection did not match any entities"
122