diff options
Diffstat (limited to 'src/Main.hs')
-rw-r--r-- | src/Main.hs | 62 |
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 | ||
3 | import Data.PQueue.Prio.Max (MaxPQueue) | 3 | import Data.PQueue.Prio.Max (MaxPQueue) |
4 | import qualified Data.PQueue.Prio.Max as MaxPQueue | 4 | import qualified Data.PQueue.Prio.Max as MaxPQueue |
@@ -9,8 +9,11 @@ import qualified Data.Sequence as Seq | |||
9 | import Data.Text (Text) | 9 | import Data.Text (Text) |
10 | import qualified Data.Text as Text | 10 | import qualified Data.Text as Text |
11 | 11 | ||
12 | import Data.Set (Set) | ||
13 | import qualified Data.Set as Set | ||
14 | |||
12 | import Data.Default.Class | 15 | import Data.Default.Class |
13 | import Data.Maybe (fromMaybe) | 16 | import Data.Maybe (fromMaybe, isNothing, fromJust) |
14 | 17 | ||
15 | import System.Environment.XDG.BaseDir (getUserCacheFile) | 18 | import System.Environment.XDG.BaseDir (getUserCacheFile) |
16 | import System.Environment (getProgName) | 19 | import 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 | |||
73 | showAssoc :: (SequenceValue, Entity) -> String | ||
74 | showAssoc (val, entity) = show val <> "\t" <> (Text.unpack $ showEntity entity) | ||
75 | |||
76 | |||
77 | apply :: SequenceM m => Alteration -> Comment -> InputT m () | ||
78 | apply alteration comment = alter alteration >> modify (\ctx -> ctx { ctxHistory = ctxHistory ctx |> (alteration, comment) }) | ||
79 | |||
80 | alter :: SequenceM m => Alteration -> InputT m () | ||
81 | alter (Modify entity ((+) -> mod)) = alterMatching entity mod | ||
82 | alter (Override entity (const -> mod)) = alterMatching entity mod | ||
83 | alter (Rename old new) = do | ||
84 | [(k, _)] <- filter (\(_, v) -> v == old) <$> gets (MaxPQueue.assocsU . ctxSequence) | ||
85 | alter (Drop old) | ||
86 | alter (Insert new k) | ||
87 | alter (Drop entity) = do | ||
88 | (matching, notMatching) <- MaxPQueue.partition (== entity) <$> gets ctxSequence | ||
89 | modify $ \ctx -> ctx { ctxSequence = notMatching } | ||
90 | when (MaxPQueue.null matching) warnEmpty | ||
91 | alter (Insert entity val) = do | ||
92 | modify $ \ctx -> ctx { ctxSequence = MaxPQueue.insert val entity $ ctxSequence ctx } | ||
93 | introduceNumbering entity | ||
94 | |||
95 | |||
96 | alterMatching :: SequenceM m => Entity -> (SequenceValue -> SequenceValue) -> InputT m () | ||
97 | alterMatching 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 | |||
102 | introduceNumbering :: SequenceM m => Entity -> InputT m () | ||
103 | introduceNumbering 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 | |||
120 | warnEmpty :: MonadIO m => InputT m () | ||
121 | warnEmpty = outputStrLn "Selection did not match any entities" | ||
122 | |||