diff options
Diffstat (limited to 'src/Main.hs')
| -rw-r--r-- | src/Main.hs | 127 |
1 files changed, 127 insertions, 0 deletions
diff --git a/src/Main.hs b/src/Main.hs new file mode 100644 index 0000000..eff9a92 --- /dev/null +++ b/src/Main.hs | |||
| @@ -0,0 +1,127 @@ | |||
| 1 | {-# LANGUAGE FlexibleContexts, ConstraintKinds, ViewPatterns, OverloadedStrings #-} | ||
| 2 | |||
| 3 | import Data.PQueue.Prio.Max (MaxPQueue) | ||
| 4 | import qualified Data.PQueue.Prio.Max as MaxPQueue | ||
| 5 | |||
| 6 | import Data.Sequence (Seq, (|>), (<|), viewl, viewr, ViewL(..), ViewR(..)) | ||
| 7 | import qualified Data.Sequence as Seq | ||
| 8 | |||
| 9 | import Data.List (delete) | ||
| 10 | import Data.Bool | ||
| 11 | |||
| 12 | import Data.Monoid (Monoid(..), (<>)) | ||
| 13 | |||
| 14 | import Data.Default.Class | ||
| 15 | |||
| 16 | import System.Console.Readline (readline) | ||
| 17 | |||
| 18 | import Control.Monad.State.Lazy (MonadState(..), runStateT, modify) | ||
| 19 | import Control.Monad.IO.Class (MonadIO(..)) | ||
| 20 | |||
| 21 | import Control.Monad (void, join) | ||
| 22 | |||
| 23 | import Control.Lens hiding ((|>), (:<)) | ||
| 24 | |||
| 25 | import Data.Text (Text) | ||
| 26 | import qualified Data.Text as Text | ||
| 27 | import qualified Data.Text.IO as Text | ||
| 28 | |||
| 29 | import Text.Read (readMaybe) | ||
| 30 | |||
| 31 | import Data.CaseInsensitive ( CI ) | ||
| 32 | import qualified Data.CaseInsensitive as CI | ||
| 33 | |||
| 34 | import System.Exit (exitSuccess) | ||
| 35 | |||
| 36 | |||
| 37 | import Types | ||
| 38 | |||
| 39 | type SequenceM m = (MonadIO m, MonadState SequenceState m) | ||
| 40 | |||
| 41 | prompt :: String | ||
| 42 | prompt = "→ " | ||
| 43 | |||
| 44 | main :: IO () | ||
| 45 | main = void $ runStateT acceptCmd def | ||
| 46 | |||
| 47 | acceptCmd :: SequenceM m => m () | ||
| 48 | acceptCmd = join $ liftIO (readline prompt) >>= handleCmd | ||
| 49 | |||
| 50 | terminate :: MonadIO m => m a | ||
| 51 | terminate = liftIO exitSuccess | ||
| 52 | |||
| 53 | handleCmd :: SequenceM m => Maybe String -> m (m ()) | ||
| 54 | handleCmd Nothing = return terminate -- EOF | ||
| 55 | handleCmd (Just "") = return acceptCmd -- Empty input | ||
| 56 | handleCmd (Just (Text.words . Text.pack -> (CI.mk -> cmd) : args)) -- Input containing at least one word | ||
| 57 | | cmd `elem` ["exit", "quit"] = return $ return () | ||
| 58 | | cmd `elem` ["insert", "add"] = acceptCmd <$ case args of | ||
| 59 | (name : (readMaybe . Text.unpack -> Just val) : comment) -> bool (liftIO $ Text.putStrLn "Did not insert new entity") (return ()) =<< withNewName (\e -> modify $ update (Insert e val, parseComment comment)) name | ||
| 60 | _ -> liftIO . Text.putStrLn $ "Malformed arguments to insert.\nExpecting: insert <name> <sequence value> [<comment> […]]" | ||
| 61 | | cmd == "dump" = acceptCmd <$ (get >>= liftIO . print) | ||
| 62 | | otherwise = acceptCmd <$ do | ||
| 63 | liftIO $ Text.putStrLn ("No such command known: " <> CI.original cmd) | ||
| 64 | handleCmd _ = error "Could not parse input String to Text" | ||
| 65 | |||
| 66 | askBool :: MonadIO m => Text -> m Bool | ||
| 67 | askBool question = do | ||
| 68 | str <- liftIO $ readline (Text.unpack question <> " (Yes/No)?\n" <> prompt) | ||
| 69 | case str of | ||
| 70 | Nothing -> terminate | ||
| 71 | Just (CI.mk -> "yes") -> return True | ||
| 72 | Just (CI.mk -> "y") -> return True | ||
| 73 | Just (CI.mk -> "no") -> return False | ||
| 74 | Just (CI.mk -> "n") -> return False | ||
| 75 | _ -> askBool question | ||
| 76 | |||
| 77 | withNewName :: SequenceM m => (Entity -> m ()) -> Text -> m Bool | ||
| 78 | withNewName callback name = do | ||
| 79 | -- names <- getNames <$> use history | ||
| 80 | entity <- getEntity | ||
| 81 | maybe False (const True) <$> maybe (return Nothing) (\e -> Just <$> callback e) entity | ||
| 82 | where | ||
| 83 | number :: MaxPQueue Integer Entity -> MaxPQueue Integer Entity | ||
| 84 | number = fst . MaxPQueue.foldrWithKey accum (MaxPQueue.empty, 0) | ||
| 85 | accum key val o@(queue, maxNmbr) | ||
| 86 | | (Entity (CI.mk -> val') _) <- val | ||
| 87 | , val' == CI.mk name = (MaxPQueue.insert key (Entity (CI.original val') (Just $ succ maxNmbr)) queue, succ maxNmbr) | ||
| 88 | | otherwise = o | ||
| 89 | getEntity = do | ||
| 90 | names <- MaxPQueue.elems <$> use queue -- we have semantic guarantees that names is a set | ||
| 91 | let | ||
| 92 | takenNumbers = map (\(Entity _ n) -> n) $ filter (\(Entity (CI.mk -> id) _) -> id == CI.mk name) names | ||
| 93 | case takenNumbers of | ||
| 94 | [] -> return . Just $ Entity name Nothing | ||
| 95 | [Nothing] -> do | ||
| 96 | liftIO $ Text.putStrLn ("Name »" <> name <> "« is already taken.") | ||
| 97 | useNumber <- liftIO $ askBool "Introduce a numbering scheme" | ||
| 98 | if useNumber | ||
| 99 | then queue <~ (number) >> getEntity | ||
| 100 | else return Nothing | ||
| 101 | (maximum -> (Just maxNmbr)) -> do | ||
| 102 | let | ||
| 103 | entity = Entity name (Just $ succ maxNmbr) | ||
| 104 | liftIO $ Text.putStrLn ("Changed name to »" <> showEntity entity <> "«") | ||
| 105 | return $ Just entity | ||
| 106 | |||
| 107 | parseComment :: [Text] -> Maybe Comment | ||
| 108 | parseComment (Text.unwords -> c) | ||
| 109 | | c == "" = Nothing | ||
| 110 | | otherwise = Just c | ||
| 111 | |||
| 112 | update :: (Alteration, Maybe Comment) -> SequenceState -> SequenceState | ||
| 113 | update loggable@(alt, _) = affect alt . over history (|> loggable) | ||
| 114 | |||
| 115 | affect :: Alteration -> SequenceState -> SequenceState | ||
| 116 | affect (Modify id by) = over queue $ affect' (\(k, v) -> if v == id then Just (k + by, id) else Just (k, v)) | ||
| 117 | affect (Override id new) = over queue $ affect' (\(k, v) -> if v == id then Just (new, id) else Just (k, v)) | ||
| 118 | affect (Drop id) = over queue $ MaxPQueue.filter (/= id) | ||
| 119 | affect (Insert id v) = over queue $ MaxPQueue.insert v id | ||
| 120 | affect _ = error "Modification not implemented yet" | ||
| 121 | |||
| 122 | affect' :: ((Integer, Entity) -> Maybe (Integer, Entity)) -> MaxPQueue Integer Entity -> MaxPQueue Integer Entity | ||
| 123 | affect' f = MaxPQueue.foldrWithKey accum MaxPQueue.empty | ||
| 124 | where | ||
| 125 | accum key val | ||
| 126 | | (Just (key', val')) <- f (key, val) = MaxPQueue.insert key' val' | ||
| 127 | | otherwise = id | ||
