diff options
Diffstat (limited to 'src/Main.hs')
| -rw-r--r-- | src/Main.hs | 77 |
1 files changed, 76 insertions, 1 deletions
diff --git a/src/Main.hs b/src/Main.hs index e9e1deb..639673c 100644 --- a/src/Main.hs +++ b/src/Main.hs | |||
| @@ -1,2 +1,77 @@ | |||
| 1 | {-# LANGUAGE ViewPatterns #-} | ||
| 2 | |||
| 3 | import Control.Monad | ||
| 4 | |||
| 5 | import Control.Lens | ||
| 6 | |||
| 7 | import System.Console.Shell | ||
| 8 | import System.Console.Shell.ShellMonad | ||
| 9 | import System.Console.Shell.Backend.Haskeline | ||
| 10 | |||
| 11 | import System.Environment.XDG.BaseDir | ||
| 12 | import System.FilePath | ||
| 13 | import System.Directory | ||
| 14 | |||
| 15 | import Data.Default | ||
| 16 | import Data.CaseInsensitive (CI) | ||
| 17 | import qualified Data.CaseInsensitive | ||
| 18 | |||
| 19 | import Data.Map.Strict (Map) | ||
| 20 | import qualified Data.Map.Strict as Map | ||
| 21 | |||
| 22 | import Data.List | ||
| 23 | import Data.Maybe | ||
| 24 | |||
| 25 | import Data.Function | ||
| 26 | |||
| 27 | import Control.Monad.State.Strict | ||
| 28 | |||
| 29 | import Sequence.Types | ||
| 30 | import Sequence.Utils | ||
| 31 | |||
| 32 | import Text.Layout.Table | ||
| 33 | |||
| 1 | main :: IO () | 34 | main :: IO () |
| 2 | main = undefined | 35 | main = do |
| 36 | historyFile <- getUserCacheFile "sequence" "history" | ||
| 37 | createDirectoryIfMissing True $ takeDirectory historyFile | ||
| 38 | let | ||
| 39 | description = initialShellDescription | ||
| 40 | { historyFile = Just historyFile | ||
| 41 | , prompt = \st -> return $ maybe "" (++ " ") ((evalState ?? st) . toName . snd <$> (listToMaybe $ view priorityQueue st)) ++ "→ " | ||
| 42 | , beforePrompt = gets stateOutline >>= (\str -> if null str then return () else shellPutStrLn str) | ||
| 43 | , commandStyle = OnlyCommands | ||
| 44 | , shellCommands = [ exitCommand "exit" | ||
| 45 | , helpCommand "help" | ||
| 46 | , cmd "factions" listFactions "List all inhabited factions" | ||
| 47 | , cmd "members" listFaction "List all members of a faction" | ||
| 48 | , cmd "entities" listEntities "List all entities" | ||
| 49 | ] | ||
| 50 | } | ||
| 51 | void $ runShell description haskelineBackend (def :: GameState) | ||
| 52 | |||
| 53 | stateOutline :: GameState -> String | ||
| 54 | stateOutline st | ||
| 55 | | null pQueue = "" | ||
| 56 | | otherwise = layoutTableToString rowGs (Just ("" : factions, repeat def)) (repeat def) unicodeBoldHeaderS | ||
| 57 | where | ||
| 58 | factions = map (view faction') $ st ^. inhabitedFactions | ||
| 59 | pQueue = st ^. priorityQueue | ||
| 60 | protoRows = groupBy ((==) `on` fst) pQueue | ||
| 61 | faction id = fromJust $ view eFaction <$> Map.lookup id (st ^. gEntities) | ||
| 62 | factionIndex id = fromJust $ elemIndex (view faction' $ faction id) factions | ||
| 63 | rowGs = do | ||
| 64 | rowGroup'@((seqVal', _):_) <- protoRows | ||
| 65 | let | ||
| 66 | rowGroup = map snd rowGroup' | ||
| 67 | factionColumn i = [evalState ?? st $ toName x | x <- rowGroup, factionIndex x == i ] | ||
| 68 | return . colsAllG top $ [show (seqVal' ^. seqVal)] : map factionColumn [0..(length factions - 1)] | ||
| 69 | |||
| 70 | listFaction :: Completable Faction -> Sh GameState () | ||
| 71 | listFaction (Completable (flip (set faction') def -> qFaction)) = use gEntities >>= mapM_ (shellPutStrLn <=< toName) . Map.keys . Map.filter ((==) qFaction . view eFaction) | ||
| 72 | |||
| 73 | listFactions :: Sh GameState () | ||
| 74 | listFactions = use inhabitedFactions >>= mapM_ (shellPutStrLn . view faction') | ||
| 75 | |||
| 76 | listEntities :: Sh GameState () | ||
| 77 | listEntities = use (gEntities . to Map.keys) >>= mapM_ (shellPutStrLn <=< toName) | ||
