From 99b5f8df7e88798325eacd2fcf5a68b4d7e75231 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Fri, 16 Feb 2018 18:12:59 +0000 Subject: [PATCH 01/22] docs (roadmap.md): added features to roadmap --- roadmap.md | 1 + 1 file changed, 1 insertion(+) diff --git a/roadmap.md b/roadmap.md index 89e5ef27..0b196eb6 100644 --- a/roadmap.md +++ b/roadmap.md @@ -27,6 +27,7 @@ ## To Do +- Task body - e.g. as well as sub lists, have a longer description - Move between lists with `m` - shows possible lists - Left/Right arrow keys in insert mode - Add tags/labels with `t` From 3def6eb1dc7cc0741edd0cf6ab61baa75dddb158 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Fri, 16 Feb 2018 18:17:29 +0000 Subject: [PATCH 02/22] docs (roadmap.md): added bug --- roadmap.md | 1 + 1 file changed, 1 insertion(+) diff --git a/roadmap.md b/roadmap.md index 0b196eb6..1e67c663 100644 --- a/roadmap.md +++ b/roadmap.md @@ -40,6 +40,7 @@ ## In Progress +- No cursor in sub-task view ## Done From 5306e96f88a3b313f3e7efbe61dfdf2d4ad5183a Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sat, 17 Feb 2018 09:59:14 +0000 Subject: [PATCH 03/22] fix (UI.Modal): added cursor to single line sub-tasks --- roadmap.md | 2 ++ src/UI/Draw.hs | 4 +++- src/UI/Modal.hs | 8 ++++++-- src/UI/Types.hs | 3 ++- 4 files changed, 13 insertions(+), 4 deletions(-) diff --git a/roadmap.md b/roadmap.md index 1e67c663..a31a194b 100644 --- a/roadmap.md +++ b/roadmap.md @@ -41,6 +41,8 @@ ## In Progress - No cursor in sub-task view + * ~Single line~ + * Multi-line ## Done diff --git a/src/UI/Draw.hs b/src/UI/Draw.hs index 66a49f48..bfea7adb 100644 --- a/src/UI/Draw.hs +++ b/src/UI/Draw.hs @@ -4,7 +4,8 @@ module UI.Draw ( chooseCursor ) where -import Events.State (State, Mode(..), InsertMode(..), Pointer, lists, current, mode, normalise) +import Events.State (lists, current, mode, normalise) +import Events.State.Types (State, Mode(..), InsertMode(..), Pointer, ModalType(..), SubTasksMode(..)) import Brick import Data.Text as T (Text, length, pack, concat, append, empty) import Data.Taskell.List (List, tasks, title) @@ -113,6 +114,7 @@ chooseCursor state = case mode s of Insert EditList -> cursor (fst c, -1) Insert CreateTask -> cursor c Insert EditTask -> cursor c + Modal (SubTasks i STInsert) -> showCursorNamed (RNModalItem i) _ -> neverShowCursor s where s = normalise state diff --git a/src/UI/Modal.hs b/src/UI/Modal.hs index 69a527bb..8d66dfba 100644 --- a/src/UI/Modal.hs +++ b/src/UI/Modal.hs @@ -10,7 +10,7 @@ import Brick import Brick.Widgets.Center import Brick.Widgets.Border import Data.Taskell.Task (SubTask, description, subTasks, name, complete) -import Data.Text as T (Text, lines, replace, breakOn, strip, drop, append) +import Data.Text as T (Text, lines, replace, breakOn, strip, drop, append, length) import Data.Text.Encoding (decodeUtf8) import Data.FileEmbed (embedFile) import Data.Foldable (toList) @@ -36,12 +36,16 @@ help = modal "Controls" w right = vBox $ txt . T.strip . T.drop 1 <$> r w = left <+> right +addCursor :: Int -> Text -> Widget ResourceName -> Widget ResourceName +addCursor li d = showCursor (RNModalItem li) (Location (T.length d + 2, 0)) + renderSubTask :: Int -> Int -> SubTask -> Widget ResourceName renderSubTask current i subtask | i == current = visible $ withAttr taskCurrentAttr widget | complete subtask = withAttr disabledAttr widget | otherwise = widget where postfix = if complete subtask then " ✓" else "" - widget = txt "• " <+> txtWrap (name subtask `append` postfix) + text = name subtask `append` postfix + widget = addCursor i text (txt "• " <+> txtWrap text) st :: State -> Maybe (Widget ResourceName) st state = do diff --git a/src/UI/Types.hs b/src/UI/Types.hs index d270f190..dae3dd31 100644 --- a/src/UI/Types.hs +++ b/src/UI/Types.hs @@ -1,10 +1,11 @@ module UI.Types where -import Events.State (Pointer) +import Events.State.Types (Pointer) data ResourceName = RNTask Pointer | RNList Int | RNLists | RNModal + | RNModalItem Int deriving (Show, Eq, Ord) From ff76ed6fd647266c8275869962257eff4230b87a Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sat, 17 Feb 2018 10:02:00 +0000 Subject: [PATCH 04/22] docs (README.md/roadmap.md): updated roadmap/readme --- README.md | 6 +++++- roadmap.md | 8 +++++++- 2 files changed, 12 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 03ccfbce..77fea171 100644 --- a/README.md +++ b/README.md @@ -41,7 +41,7 @@ Run `sudo dnf install ncurses-compat-libs` then download and run binary as descr Press `?` for a [list of controls](https://github.com/smallhadroncollider/taskell/blob/master/templates/controls.md) -### Tips +## Tips - If you're using a simple two-column "To Do" and "Done" then use the space bar to mark an item as complete while staying in the "To Do" list. If you're using a more complicated column setup then you will want to use `H`/`L` to move tasks between columns. @@ -95,3 +95,7 @@ The available colours are: `black`, `red`, `green`, `yellow`, `blue`, `magenta`, ## Roadmap See [roadmap.md](https://github.com/smallhadroncollider/taskell/blob/develop/roadmap.md) for planned features + +## Contributing + +Please check the [roadmap.md](https://github.com/smallhadroncollider/taskell/blob/develop/roadmap.md) before adding any bugs/feature requests to Issues. diff --git a/roadmap.md b/roadmap.md index a31a194b..110bd2a3 100644 --- a/roadmap.md +++ b/roadmap.md @@ -17,17 +17,23 @@ ## Bugs -- Items near bottom of the list jump in position +- Feels sluggish in sub-task view - cache main view? - Up and down in search gets a bit lost - Editing list title doesn't always have visibility - Vertical spacing doesn't work if the current item is blank - Cursor goes missing on the left hand side at the end of a line - One bad config line stops all config from working - needs to merge with defaultConfig - Help modal needs to scroll on smaller windows +- Sub-task count not visible on last item in a list longer than the vertical height ## To Do - Task body - e.g. as well as sub lists, have a longer description +- Customisable Markdown format + * Change top level headers + * Change top level list item: e.g. to H3 instead of li + * Change sub-list: e.g. from " *" to "-" + * Change body - Move between lists with `m` - shows possible lists - Left/Right arrow keys in insert mode - Add tags/labels with `t` From fc692a33d7630cf441889cae1fe6630073877b9a Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sat, 17 Feb 2018 10:11:11 +0000 Subject: [PATCH 05/22] refactor (UI.Draw): pulled main image out into separate function to make caching easier --- src/UI/Draw.hs | 26 +++++++++++++++----------- 1 file changed, 15 insertions(+), 11 deletions(-) diff --git a/src/UI/Draw.hs b/src/UI/Draw.hs index bfea7adb..c7dfeb1f 100644 --- a/src/UI/Draw.hs +++ b/src/UI/Draw.hs @@ -90,19 +90,23 @@ searchImage layout s i = case mode s of ) _ -> i +main :: LayoutConfig -> State -> Widget ResourceName +main layout s = + searchImage layout s + . viewport RNLists Horizontal + . hLimit (Seq.length ls * colWidth layout) + . padTopBottom 1 + . hBox + . toList + $ renderList layout (current s) `Seq.mapWithIndex` ls + + where ls = lists s + -- draw draw :: LayoutConfig -> State -> [Widget ResourceName] -draw layout state = showModal state [main] - where s = normalise state - ls = lists s - main = - searchImage layout state - . viewport RNLists Horizontal - . hLimit (Seq.length ls * colWidth layout) - . padTopBottom 1 - . hBox - . toList - $ renderList layout (current s) `Seq.mapWithIndex` ls +draw layout state = + let s = normalise state in + showModal s [main layout s] -- cursors cursor :: (Int, Int) -> [CursorLocation ResourceName] -> Maybe (CursorLocation ResourceName) From caac140015a586fd627cd64f59a135ab7fa59c5f Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sat, 17 Feb 2018 10:25:23 +0000 Subject: [PATCH 06/22] fix (UI.Modal): got multiline cursors working in sub-tasks list --- roadmap.md | 6 +++--- src/UI/Modal.hs | 23 +++++++++++++++++------ 2 files changed, 20 insertions(+), 9 deletions(-) diff --git a/roadmap.md b/roadmap.md index 110bd2a3..c9a834a4 100644 --- a/roadmap.md +++ b/roadmap.md @@ -46,9 +46,6 @@ ## In Progress -- No cursor in sub-task view - * ~Single line~ - * Multi-line ## Done @@ -133,3 +130,6 @@ * ~Word wrapping~ * ~Searching~ * ~Delete items~ +- No cursor in sub-task view + * ~Single line~ + * ~Multi-line~ diff --git a/src/UI/Modal.hs b/src/UI/Modal.hs index 8d66dfba..d12fd408 100644 --- a/src/UI/Modal.hs +++ b/src/UI/Modal.hs @@ -10,8 +10,9 @@ import Brick import Brick.Widgets.Center import Brick.Widgets.Border import Data.Taskell.Task (SubTask, description, subTasks, name, complete) -import Data.Text as T (Text, lines, replace, breakOn, strip, drop, append, length) +import Data.Text as T (Text, lines, replace, breakOn, strip, drop, length) import Data.Text.Encoding (decodeUtf8) +import Data.Taskell.Text (wrap) import Data.FileEmbed (embedFile) import Data.Foldable (toList) import Data.Sequence (mapWithIndex) @@ -20,8 +21,11 @@ import IO.Markdown (trimListItem) import UI.Types (ResourceName(..)) import UI.Theme (titleAttr, taskCurrentAttr, disabledAttr) +width :: Int +width = 50 + place :: Widget ResourceName -> Widget ResourceName -place = padTopBottom 1 . centerLayer . border . padTopBottom 1 . padLeftRight 4 . hLimit 50 +place = padTopBottom 1 . centerLayer . border . padTopBottom 1 . padLeftRight 4 . hLimit width modal :: Text -> Widget ResourceName -> Widget ResourceName modal title w = place $ t <=> w' @@ -36,16 +40,23 @@ help = modal "Controls" w right = vBox $ txt . T.strip . T.drop 1 <$> r w = left <+> right -addCursor :: Int -> Text -> Widget ResourceName -> Widget ResourceName -addCursor li d = showCursor (RNModalItem li) (Location (T.length d + 2, 0)) +addCursor :: Int -> [Text] -> Widget ResourceName -> Widget ResourceName +addCursor li d = showCursor n (Location (h, v)) + + where v = Prelude.length d - 1 + h = T.length $ last d + n = RNModalItem li + +box :: [Text] -> Widget ResourceName +box d = padBottom (Pad 1) . vBox $ txt <$> d renderSubTask :: Int -> Int -> SubTask -> Widget ResourceName renderSubTask current i subtask | i == current = visible $ withAttr taskCurrentAttr widget | complete subtask = withAttr disabledAttr widget | otherwise = widget where postfix = if complete subtask then " ✓" else "" - text = name subtask `append` postfix - widget = addCursor i text (txt "• " <+> txtWrap text) + text = wrap (width - 6) $ name subtask + widget = txt "• " <+> addCursor i text (box text) <+> txt postfix st :: State -> Maybe (Widget ResourceName) st state = do From 1aed5888cae2394d5c51db3b8381e80f6b78a532 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sat, 17 Feb 2018 13:46:35 +0000 Subject: [PATCH 07/22] fix (UI.Modal): improved wrapping for Modals --- src/UI/Modal.hs | 51 +++++++++++++++++++++++++++++-------------------- 1 file changed, 30 insertions(+), 21 deletions(-) diff --git a/src/UI/Modal.hs b/src/UI/Modal.hs index d12fd408..f9ef86d4 100644 --- a/src/UI/Modal.hs +++ b/src/UI/Modal.hs @@ -16,27 +16,35 @@ import Data.Taskell.Text (wrap) import Data.FileEmbed (embedFile) import Data.Foldable (toList) import Data.Sequence (mapWithIndex) +import Data.Maybe (fromMaybe) import IO.Markdown (trimListItem) import UI.Types (ResourceName(..)) import UI.Theme (titleAttr, taskCurrentAttr, disabledAttr) -width :: Int -width = 50 +maxWidth :: Int +maxWidth = 50 -place :: Widget ResourceName -> Widget ResourceName -place = padTopBottom 1 . centerLayer . border . padTopBottom 1 . padLeftRight 4 . hLimit width - -modal :: Text -> Widget ResourceName -> Widget ResourceName -modal title w = place $ t <=> w' - where t = padLeftRight 2 . padBottom (Pad 1) . withAttr titleAttr $ txtWrap title +modal :: Int -> (Text, Widget ResourceName) -> Widget ResourceName +modal width (title, w) = t <=> w' + where t = padLeftRight 2 . padBottom (Pad 1) . withAttr titleAttr $ box (wrap width title) w'= viewport RNModal Vertical w -help :: Widget ResourceName -help = modal "Controls" w +surround :: (Int -> (Text, Widget ResourceName)) -> Widget ResourceName +surround fn = Widget Fixed Fixed $ do + ctx <- getContext + let fullWidth = availWidth ctx + padding = 4 + w = (if fullWidth > maxWidth then maxWidth else fullWidth) - (padding * 2) + widget = modal (w - 4) $ fn w + render . padTopBottom 1 . centerLayer . border . padTopBottom 1 . padLeftRight padding . hLimit w $ widget + + +help :: Int -> (Text, Widget ResourceName) +help _ = ("Controls", w) where ls = T.lines $ decodeUtf8 $(embedFile "templates/controls.md") (l, r) = unzip $ breakOn ":" . T.replace "`" "" . trimListItem <$> ls - left = padRight (Pad 2) . vBox $ withAttr taskCurrentAttr . txt <$> l + left = padLeftRight 2 . vBox $ withAttr taskCurrentAttr . txt <$> l right = vBox $ txt . T.strip . T.drop 1 <$> r w = left <+> right @@ -50,29 +58,30 @@ addCursor li d = showCursor n (Location (h, v)) box :: [Text] -> Widget ResourceName box d = padBottom (Pad 1) . vBox $ txt <$> d -renderSubTask :: Int -> Int -> SubTask -> Widget ResourceName -renderSubTask current i subtask | i == current = visible $ withAttr taskCurrentAttr widget +renderSubTask :: Int -> Int -> Int -> SubTask -> Widget ResourceName +renderSubTask width current i subtask | i == current = visible $ withAttr taskCurrentAttr widget | complete subtask = withAttr disabledAttr widget | otherwise = widget where postfix = if complete subtask then " ✓" else "" text = wrap (width - 6) $ name subtask widget = txt "• " <+> addCursor i text (box text) <+> txt postfix -st :: State -> Maybe (Widget ResourceName) -st state = do +st' :: State -> Int -> Maybe (Text, Widget ResourceName) +st' state width = do task <- getCurrentTask state index <- getCurrentSubTask state let sts = subTasks task w | null sts = withAttr disabledAttr $ txt " No sub-tasks" - | otherwise = vBox . toList $ renderSubTask index `mapWithIndex` sts - return $ modal (description task) w + | otherwise = vBox . toList $ renderSubTask width index `mapWithIndex` sts + return (description task, w) + +st :: State -> Int -> (Text, Widget ResourceName) +st state width = fromMaybe ("Error", txt "Oops") $ st' state width getModal :: State -> ModalType -> [Widget ResourceName] getModal s t = case t of - Help -> [help] - SubTasks _ _ -> case st s of - Just w -> [w] - Nothing -> [] + Help -> [surround help] + SubTasks _ _ -> [surround $ st s] showModal :: State -> [Widget ResourceName] -> [Widget ResourceName] showModal s view = case mode s of From 22b052f53ed44911af252c13ee8726e56c750ab7 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 12:23:44 +0000 Subject: [PATCH 08/22] feat (IO.Markdown/IO.Config): added Markdown formatting options --- app/Main.hs | 2 +- src/App.hs | 16 +++++++------- src/IO/Config.hs | 30 ++++++++++++++++++++++--- src/IO/Markdown.hs | 52 +++++++++++++++++++++++++++++--------------- src/IO/Taskell.hs | 24 ++++++++++---------- templates/config.ini | 5 +++++ 6 files changed, 87 insertions(+), 42 deletions(-) diff --git a/app/Main.hs b/app/Main.hs index 7b86744d..8f20dc1e 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -10,7 +10,7 @@ import App (go) -- read file then render start :: Config -> FilePath -> IO () start config path = do - state <- create path <$> IO.Taskell.readFile path + state <- create path <$> IO.Taskell.readFile config path go config state -- if taskell.md exists/created then start diff --git a/src/App.hs b/src/App.hs index 5afea453..961c77a4 100644 --- a/src/App.hs +++ b/src/App.hs @@ -16,23 +16,23 @@ import UI.Draw (draw, chooseCursor) import UI.Types (ResourceName(..)) -- store -store :: Lists -> State -> IO State -store ls s = do - forkIO $ IO.Taskell.writeFile ls (path s) +store :: Config -> Lists -> State -> IO State +store config ls s = do + forkIO $ IO.Taskell.writeFile config ls (path s) return (Events.State.continue s) -- App code -handleEvent :: State -> BrickEvent ResourceName e -> EventM ResourceName (Next State) -handleEvent s' (VtyEvent e) = let s = event e s' in +handleEvent :: Config -> State -> BrickEvent ResourceName e -> EventM ResourceName (Next State) +handleEvent config s' (VtyEvent e) = let s = event e s' in case mode s of Shutdown -> Brick.halt s _ -> case io s of - Just ls -> liftIO (store ls s) >>= Brick.continue + Just ls -> liftIO (store config ls s) >>= Brick.continue Nothing -> Brick.continue s -handleEvent s _ = Brick.continue s +handleEvent _ s _ = Brick.continue s go :: Config -> State -> IO () go config initial = do attrMap' <- const <$> generateAttrMap - let app = App (draw $ layout config) chooseCursor handleEvent return attrMap' + let app = App (draw $ layout config) chooseCursor (handleEvent config) return attrMap' void (defaultMain app initial) diff --git a/src/IO/Config.hs b/src/IO/Config.hs index 9a0c512d..06020a4f 100644 --- a/src/IO/Config.hs +++ b/src/IO/Config.hs @@ -4,13 +4,13 @@ module IO.Config where import System.Directory import Data.Ini.Config - import Data.FileEmbed (embedFile) import qualified Data.ByteString as B (writeFile) import UI.Theme import Brick.Themes (themeToAttrMap, loadCustomizations) import Brick (AttrMap) +import Data.Text (Text, strip, dropAround) import qualified Data.Text.IO as T data GeneralConfig = GeneralConfig { @@ -22,9 +22,16 @@ data LayoutConfig = LayoutConfig { columnPadding :: Int } +data MarkdownConfig = MarkdownConfig { + titleOutput :: Text, + taskOutput :: Text, + subtaskOutput :: Text + } + data Config = Config { general :: GeneralConfig, - layout :: LayoutConfig + layout :: LayoutConfig, + markdown :: MarkdownConfig } defaultConfig :: Config @@ -35,9 +42,17 @@ defaultConfig = Config { layout = LayoutConfig { columnWidth = 24, columnPadding = 3 + }, + markdown = MarkdownConfig { + titleOutput = "##", + taskOutput = "-", + subtaskOutput = " *" } } +parseString :: Text -> Text +parseString = dropAround (== '"') . strip + getDir :: IO FilePath getDir = (++ "/.taskell") <$> getHomeDirectory @@ -81,7 +96,16 @@ configParser = do columnWidthCf <- fieldOf "column_width" number columnPaddingCf <- fieldOf "column_padding" number return LayoutConfig { columnWidth = columnWidthCf, columnPadding = columnPaddingCf } - return Config { general = generalCf, layout = layoutCf } + markdownCf <- section "markdown" $ do + titleOutputCf <- parseString <$> fieldOf "title" string + taskOutputCf <- parseString <$> fieldOf "task" string + subtaskOutputCf <- parseString <$> fieldOf "subtask" string + return MarkdownConfig { + titleOutput = titleOutputCf, + taskOutput = taskOutputCf, + subtaskOutput = subtaskOutputCf + } + return Config { general = generalCf, layout = layoutCf, markdown = markdownCf } getConfig :: IO Config getConfig = do diff --git a/src/IO/Markdown.hs b/src/IO/Markdown.hs index d6a29fc7..1b44418e 100644 --- a/src/IO/Markdown.hs +++ b/src/IO/Markdown.hs @@ -5,7 +5,7 @@ module IO.Markdown ( trimListItem ) where -import Data.Text (Text, drop, append, null, lines, isPrefixOf, strip, dropAround) +import Data.Text (Text, drop, append, null, lines, isPrefixOf, strip, dropAround, snoc) import Data.Text.Encoding (encodeUtf8, decodeUtf8With) import Data.Taskell.Lists (Lists, newList, appendToLast) @@ -16,6 +16,8 @@ import Data.Sequence (empty, adjust') import Data.ByteString (ByteString) import Data.Word (Word8) +import IO.Config (Config, MarkdownConfig, markdown, titleOutput, taskOutput, subtaskOutput) + -- parse code trimListItem :: Text -> Text trimListItem = strip . Data.Text.drop 1 @@ -37,37 +39,51 @@ addSubItem t ls = adjust' updateList i ls updateList l = updateFn j (addSubTask st) l where j = count l - 1 -start :: Lists -> Text -> Lists -start ls s | "##" `isPrefixOf` s = newList (trimTitle s) ls - | "-" `isPrefixOf` s = appendToLast (trimTask s) ls - | " *" `isPrefixOf` s = addSubItem (trimListItem $ strip s) ls - | otherwise = ls +start :: MarkdownConfig -> Lists -> Text -> Lists +start config ls s | titleOutput config `snoc` ' ' `isPrefixOf` s = newList (trimTitle s) ls + | taskOutput config `snoc` ' ' `isPrefixOf` s = appendToLast (trimTask s) ls + | subtaskOutput config `snoc` ' ' `isPrefixOf` s = addSubItem (trimListItem $ strip s) ls + | otherwise = ls decodeError :: String -> Maybe Word8 -> Maybe Char decodeError _ _ = Just '\65533' -parse :: ByteString -> Lists -parse s = foldl' start empty $ Data.Text.lines $ decodeUtf8With decodeError s +parse :: Config -> ByteString -> Lists +parse config s = foldl' (start (markdown config)) empty $ Data.Text.lines $ decodeUtf8With decodeError s -- stringify code join :: Text -> [Text] -> Text join = foldl' Data.Text.append -subTaskToString :: Text -> SubTask -> Text -subTaskToString t st = join t [" * ", surround, name st, surround, "\n"] +subTaskToString :: MarkdownConfig -> Text -> SubTask -> Text +subTaskToString config t st = join t [ + subtaskOutput config, + " ", + surround, + name st, + surround, + "\n" + ] where surround = if complete st then "~" else "" -taskToString :: Text -> Task -> Text -taskToString s t = join s ["- ", description t, "\n", foldl' subTaskToString "" (subTasks t)] +taskToString :: MarkdownConfig -> Text -> Task -> Text +taskToString config s t = join s [ + taskOutput config, + " ", + description t, + "\n", + foldl' (subTaskToString config) "" (subTasks t) + ] -listToString :: Text -> List -> Text -listToString s l = join s [ +listToString :: MarkdownConfig -> Text -> List -> Text +listToString config s l = join s [ if Data.Text.null s then "" else "\n" - , "## " + , titleOutput config + , " " , title l , "\n\n" - , foldl' taskToString "" (tasks l) + , foldl' (taskToString config) "" (tasks l) ] -stringify :: Lists -> ByteString -stringify ls = encodeUtf8 $ foldl' listToString "" ls +stringify :: Config -> Lists -> ByteString +stringify config ls = encodeUtf8 $ foldl' (listToString (markdown config)) "" ls diff --git a/src/IO/Taskell.hs b/src/IO/Taskell.hs index f806ca0a..37e4663b 100644 --- a/src/IO/Taskell.hs +++ b/src/IO/Taskell.hs @@ -21,27 +21,27 @@ exists :: Config -> IO (Bool, FilePath) exists c = do path <- getPath c e <- doesFileExist path - success <- promptCreate e path + success <- promptCreate c e path return (success, path) -- prompt whether to create taskell.json -promptCreate :: Bool -> String -> IO Bool -promptCreate True _ = return True -promptCreate False path = do +promptCreate :: Config -> Bool -> String -> IO Bool +promptCreate _ True _ = return True +promptCreate config False path = do cwd <- getCurrentDirectory r <- promptYN $ "Create " ++ cwd ++ "/" ++ path ++ "?" - if r then createPath path >> return True else return False + if r then createPath config path >> return True else return False -- creates taskell file -createPath :: FilePath -> IO () -createPath = writeFile initial +createPath :: Config -> FilePath -> IO () +createPath config = writeFile config initial -- writes Tasks to json file -writeFile :: Lists -> FilePath -> IO () -writeFile tasks path = void (BS.writeFile path $ stringify tasks) +writeFile :: Config -> Lists -> FilePath -> IO () +writeFile config tasks path = void (BS.writeFile path $ stringify config tasks) -- reads json file -readFile :: FilePath -> IO Lists -readFile path = do +readFile :: Config -> FilePath -> IO Lists +readFile config path = do content <- BS.readFile path - return $ parse content + return $ parse config content diff --git a/templates/config.ini b/templates/config.ini index 64375775..a8bb58da 100644 --- a/templates/config.ini +++ b/templates/config.ini @@ -4,3 +4,8 @@ filename = taskell.md [layout] column_width = 24 column_padding = 3 + +[markdown] +title = "##" +task = "-" +subtask = " *" From 083bb7a6f3ea44c1a9c5d3ea01c17a2878edd0bf Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 12:27:42 +0000 Subject: [PATCH 09/22] docs (roadmap.md): updated roadmap --- roadmap.md | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/roadmap.md b/roadmap.md index c9a834a4..1cb89541 100644 --- a/roadmap.md +++ b/roadmap.md @@ -17,23 +17,20 @@ ## Bugs +- One bad config line stops all config from working - needs to merge with defaultConfig - Feels sluggish in sub-task view - cache main view? - Up and down in search gets a bit lost - Editing list title doesn't always have visibility - Vertical spacing doesn't work if the current item is blank -- Cursor goes missing on the left hand side at the end of a line -- One bad config line stops all config from working - needs to merge with defaultConfig +- Cursor goes missing on the left hand side at the end of a line - needs to wrap - Help modal needs to scroll on smaller windows - Sub-task count not visible on last item in a list longer than the vertical height +- Pressing Enter on empty list shows an subtasks box with an error +- Empty tasks - i.e. just a space - don't show up ## To Do - Task body - e.g. as well as sub lists, have a longer description -- Customisable Markdown format - * Change top level headers - * Change top level list item: e.g. to H3 instead of li - * Change sub-list: e.g. from " *" to "-" - * Change body - Move between lists with `m` - shows possible lists - Left/Right arrow keys in insert mode - Add tags/labels with `t` @@ -133,3 +130,7 @@ - No cursor in sub-task view * ~Single line~ * ~Multi-line~ +- Customisable Markdown format + * ~Change top level headers~ + * ~Change top level list item: e.g. to H3 instead of li~ + * ~Change sub-list: e.g. from " *" to "-"~ From dbd643b59b2b2daccf58629aae1cef63df5724ac Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 14:37:36 +0000 Subject: [PATCH 10/22] docs (README.md): add configuration documentation --- README.md | 45 +++++++++++++++++++++++++++++++++++++++++++++ roadmap.md | 3 ++- 2 files changed, 47 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index 77fea171..ef9746b6 100644 --- a/README.md +++ b/README.md @@ -59,6 +59,51 @@ By default stores in a `taskell.md` file in the working directory: - Do That ``` +## Configuration + +You can edit Taskell's settings by editing `~/.taskell/config.ini`: + +```ini +[general] +; the default filename to create/look for +filename = taskell.md + +[layout] +; the width of a column +column_width = 24 + +; the padding of a column +; for both sides, so 3 would give a gap of 6 between two columns +column_padding = 3 + +[markdown] +; the markdown to start a title line with +title = "##" + +; the markdown to start a task line with +task = "-" + +; the markdown to start a sub-task line with +subtask = " *" +``` + +Make sure that the values in the `[markdown]` section are surrounded by **double**-quotes. + +If you always use sub-tasks, an alternative setup for `[markdown]` might be: + +```ini +[markdown] +title = "##" + +; each task is a header +task = "###" + +; subtasks are list items under the header +subtask = "-" +``` + +**Warning**: currently if you change your `[markdown]` settings any older files stored with different settings will not be readable. + ## Theming You can edit Taskell's colour-scheme by editing `~/.taskell/theme.ini`: diff --git a/roadmap.md b/roadmap.md index 1cb89541..1e051389 100644 --- a/roadmap.md +++ b/roadmap.md @@ -17,7 +17,6 @@ ## Bugs -- One bad config line stops all config from working - needs to merge with defaultConfig - Feels sluggish in sub-task view - cache main view? - Up and down in search gets a bit lost - Editing list title doesn't always have visibility @@ -31,6 +30,7 @@ ## To Do - Task body - e.g. as well as sub lists, have a longer description +- Display a warning if any line of the file could not be parsed - otherwise could lead to data loss - Move between lists with `m` - shows possible lists - Left/Right arrow keys in insert mode - Add tags/labels with `t` @@ -43,6 +43,7 @@ ## In Progress +- One bad config line stops all config from working - needs to merge with defaultConfig ## Done From 709cbda7d57751ee38cc9c3a3365de8219cd4e1a Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 14:44:25 +0000 Subject: [PATCH 11/22] refactor (Main.hs): simplified Main --- app/Main.hs | 15 ++++----------- 1 file changed, 4 insertions(+), 11 deletions(-) diff --git a/app/Main.hs b/app/Main.hs index 8f20dc1e..04a81dd8 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -2,20 +2,13 @@ module Main where import Control.Monad (when) import Events.State (create) -import IO.Taskell (exists, readFile) -import IO.Config (Config, setup) +import qualified IO.Taskell as T (exists, readFile) +import IO.Config (setup) import App (go) --- read file then render -start :: Config -> FilePath -> IO () -start config path = do - state <- create path <$> IO.Taskell.readFile config path - go config state - --- if taskell.md exists/created then start main :: IO () main = do config <- setup - (ex, path) <- exists config - when ex $ start config path + (exists, path) <- T.exists config + when exists $ create path <$> T.readFile config path >>= go config From 4ab5d92c1b8b017798b2f42e40983e369d33210b Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 16:33:19 +0000 Subject: [PATCH 12/22] chore (.bin/taskell): updated run script to remove .ini files --- .bin/taskell | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/.bin/taskell b/.bin/taskell index 6b465559..14ad019c 100755 --- a/.bin/taskell +++ b/.bin/taskell @@ -1 +1,4 @@ -stack build --fast --trace && stack exec taskell $@ +rm ~/.taskell/config.ini +rm ~/.taskell/theme.ini +stack build --fast --trace +stack exec taskell $@ From 866497a3ea68725a91ff92afcb166285ca28e219 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 17:46:00 +0000 Subject: [PATCH 13/22] fix (UI.Draw): added widget caching --- roadmap.md | 2 +- src/App.hs | 19 +++++++++++++++---- src/UI/Draw.hs | 6 ++++-- 3 files changed, 20 insertions(+), 7 deletions(-) diff --git a/roadmap.md b/roadmap.md index 1e051389..90ddf3ff 100644 --- a/roadmap.md +++ b/roadmap.md @@ -17,7 +17,6 @@ ## Bugs -- Feels sluggish in sub-task view - cache main view? - Up and down in search gets a bit lost - Editing list title doesn't always have visibility - Vertical spacing doesn't work if the current item is blank @@ -135,3 +134,4 @@ * ~Change top level headers~ * ~Change top level list item: e.g. to H3 instead of li~ * ~Change sub-list: e.g. from " *" to "-"~ +- Feels sluggish in sub-task view - cache main view? diff --git a/src/App.hs b/src/App.hs index 961c77a4..b7c43f7c 100644 --- a/src/App.hs +++ b/src/App.hs @@ -3,9 +3,10 @@ module App (go) where import Control.Monad (void) import Control.Monad.IO.Class (liftIO) import Control.Concurrent (forkIO) -import Events.State (State, Mode(..), continue, path, mode, io) +import Events.State (State, Mode(..), continue, path, mode, io, current) import Data.Taskell.Lists (Lists) import Brick +import Graphics.Vty.Input.Events (Event(..)) import IO.Taskell (writeFile) import IO.Config (Config, layout, generateAttrMap) @@ -21,14 +22,24 @@ store config ls s = do forkIO $ IO.Taskell.writeFile config ls (path s) return (Events.State.continue s) +next :: Config -> State -> EventM ResourceName (Next State) +next config s = case io s of + Just ls -> liftIO (store config ls s) >>= Brick.continue + Nothing -> Brick.continue s + +clearCache :: State -> EventM ResourceName () +clearCache state = do + let (li, ti) = current state + invalidateCacheEntry (RNList li) + invalidateCacheEntry (RNTask (li, ti)) + -- App code handleEvent :: Config -> State -> BrickEvent ResourceName e -> EventM ResourceName (Next State) +handleEvent _ s (VtyEvent (EvResize _ _ )) = invalidateCache >> Brick.continue s handleEvent config s' (VtyEvent e) = let s = event e s' in case mode s of Shutdown -> Brick.halt s - _ -> case io s of - Just ls -> liftIO (store config ls s) >>= Brick.continue - Nothing -> Brick.continue s + _ -> clearCache s' >> clearCache s >> next config s handleEvent _ s _ = Brick.continue s go :: Config -> State -> IO () diff --git a/src/UI/Draw.hs b/src/UI/Draw.hs index c7dfeb1f..adc4d42e 100644 --- a/src/UI/Draw.hs +++ b/src/UI/Draw.hs @@ -45,7 +45,8 @@ subTaskCount t | hasSubTasks t = T.concat [ renderTask :: LayoutConfig -> Pointer -> Int -> Int -> Task -> Widget ResourceName renderTask layout p li ti t = - padBottom (Pad 1) + cached (RNTask (li, ti)) + . padBottom (Pad 1) . (<=> (withAttr disabledAttr $ txt after)) . (if (li, ti) == p then withAttr taskCurrentAttr . visible else withAttr taskAttr) . addCursor li ti d @@ -69,7 +70,8 @@ renderTitle layout (p, i) li l = if p /= li || i == 0 then visible title' else t renderList :: LayoutConfig -> Pointer -> Int -> List -> Widget ResourceName renderList layout p li l = if fst p == li then visible list else list where list = - padLeftRight (columnPadding layout) + cached (RNList li) + . padLeftRight (columnPadding layout) . hLimit (columnWidth layout) . viewport (RNList li) Vertical . vBox From 8de1ae20766c7b087cb2fd865935069f38b36937 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 17:52:13 +0000 Subject: [PATCH 14/22] fix (App): fixed view caching in search --- src/App.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/App.hs b/src/App.hs index b7c43f7c..8c7a4563 100644 --- a/src/App.hs +++ b/src/App.hs @@ -39,6 +39,7 @@ handleEvent _ s (VtyEvent (EvResize _ _ )) = invalidateCache >> Brick.continue s handleEvent config s' (VtyEvent e) = let s = event e s' in case mode s of Shutdown -> Brick.halt s + Search _ _ -> invalidateCache >> Brick.continue s _ -> clearCache s' >> clearCache s >> next config s handleEvent _ s _ = Brick.continue s From d677b8ed5b44bf3faeaea2d569254d91a2d6329d Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sun, 18 Feb 2018 17:53:08 +0000 Subject: [PATCH 15/22] docs (roadmap.md): updated bugs --- roadmap.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/roadmap.md b/roadmap.md index 90ddf3ff..11fcf043 100644 --- a/roadmap.md +++ b/roadmap.md @@ -17,6 +17,7 @@ ## Bugs +- Leaving search only refreshes current list - Up and down in search gets a bit lost - Editing list title doesn't always have visibility - Vertical spacing doesn't work if the current item is blank @@ -29,7 +30,6 @@ ## To Do - Task body - e.g. as well as sub lists, have a longer description -- Display a warning if any line of the file could not be parsed - otherwise could lead to data loss - Move between lists with `m` - shows possible lists - Left/Right arrow keys in insert mode - Add tags/labels with `t` @@ -43,6 +43,7 @@ ## In Progress - One bad config line stops all config from working - needs to merge with defaultConfig +- Display a warning if any line of the file could not be parsed - otherwise could lead to data loss ## Done From 92623547a4666a26133d8c2dd9f77e370355cb70 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sat, 17 Feb 2018 13:37:57 +0000 Subject: [PATCH 16/22] fix (App): fixed remaining search list refreshing issues --- roadmap.md | 2 +- src/App.hs | 22 +++++++++++++++------- 2 files changed, 16 insertions(+), 8 deletions(-) diff --git a/roadmap.md b/roadmap.md index 11fcf043..40de57d3 100644 --- a/roadmap.md +++ b/roadmap.md @@ -17,7 +17,6 @@ ## Bugs -- Leaving search only refreshes current list - Up and down in search gets a bit lost - Editing list title doesn't always have visibility - Vertical spacing doesn't work if the current item is blank @@ -136,3 +135,4 @@ * ~Change top level list item: e.g. to H3 instead of li~ * ~Change sub-list: e.g. from " *" to "-"~ - Feels sluggish in sub-task view - cache main view? +- Leaving search only refreshes current list diff --git a/src/App.hs b/src/App.hs index 8c7a4563..e296585c 100644 --- a/src/App.hs +++ b/src/App.hs @@ -33,15 +33,23 @@ clearCache state = do invalidateCacheEntry (RNList li) invalidateCacheEntry (RNTask (li, ti)) +handleVtyEvent :: Config -> State -> Event -> EventM ResourceName (Next State) +handleVtyEvent config previousState e = do + let state = event e previousState + + case mode previousState of + Search _ _ -> invalidateCache + _ -> return () + + case mode state of + Shutdown -> Brick.halt state + _ -> clearCache previousState >> clearCache state >> next config state + -- App code handleEvent :: Config -> State -> BrickEvent ResourceName e -> EventM ResourceName (Next State) -handleEvent _ s (VtyEvent (EvResize _ _ )) = invalidateCache >> Brick.continue s -handleEvent config s' (VtyEvent e) = let s = event e s' in - case mode s of - Shutdown -> Brick.halt s - Search _ _ -> invalidateCache >> Brick.continue s - _ -> clearCache s' >> clearCache s >> next config s -handleEvent _ s _ = Brick.continue s +handleEvent _ state (VtyEvent (EvResize _ _ )) = invalidateCache >> Brick.continue state +handleEvent config state (VtyEvent ev) = handleVtyEvent config state ev +handleEvent _ state _ = Brick.continue state go :: Config -> State -> IO () go config initial = do From 89c71e5c83228b4d437630969f19f28dde23de9b Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Mon, 19 Feb 2018 09:41:52 +0000 Subject: [PATCH 17/22] style (UI.Modal): updated sub-task list styling --- src/UI/Modal.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/UI/Modal.hs b/src/UI/Modal.hs index f9ef86d4..06a6fe3c 100644 --- a/src/UI/Modal.hs +++ b/src/UI/Modal.hs @@ -10,7 +10,7 @@ import Brick import Brick.Widgets.Center import Brick.Widgets.Border import Data.Taskell.Task (SubTask, description, subTasks, name, complete) -import Data.Text as T (Text, lines, replace, breakOn, strip, drop, length) +import Data.Text as T (Text, lines, replace, breakOn, strip, drop, length, append) import Data.Text.Encoding (decodeUtf8) import Data.Taskell.Text (wrap) import Data.FileEmbed (embedFile) @@ -27,7 +27,7 @@ maxWidth = 50 modal :: Int -> (Text, Widget ResourceName) -> Widget ResourceName modal width (title, w) = t <=> w' - where t = padLeftRight 2 . padBottom (Pad 1) . withAttr titleAttr $ box (wrap width title) + where t = padBottom (Pad 1) . withAttr titleAttr $ box (wrap width title) w'= viewport RNModal Vertical w surround :: (Int -> (Text, Widget ResourceName)) -> Widget ResourceName @@ -36,7 +36,7 @@ surround fn = Widget Fixed Fixed $ do let fullWidth = availWidth ctx padding = 4 w = (if fullWidth > maxWidth then maxWidth else fullWidth) - (padding * 2) - widget = modal (w - 4) $ fn w + widget = modal w $ fn w render . padTopBottom 1 . centerLayer . border . padTopBottom 1 . padLeftRight padding . hLimit w $ widget @@ -63,8 +63,8 @@ renderSubTask width current i subtask | i == current = visible $ withAttr taskCu | complete subtask = withAttr disabledAttr widget | otherwise = widget where postfix = if complete subtask then " ✓" else "" - text = wrap (width - 6) $ name subtask - widget = txt "• " <+> addCursor i text (box text) <+> txt postfix + text = wrap width $ name subtask `T.append` postfix + widget = addCursor i text (box text) st' :: State -> Int -> Maybe (Text, Widget ResourceName) st' state width = do From 2c29ebc4e0e40f5f70141b802536a3171ece7c29 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Sat, 17 Feb 2018 13:37:57 +0000 Subject: [PATCH 18/22] docs (roadmap.md): added bugs --- roadmap.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/roadmap.md b/roadmap.md index 40de57d3..3318d8c1 100644 --- a/roadmap.md +++ b/roadmap.md @@ -14,6 +14,8 @@ - Remove duplication of config - currently using ini and hard-coded - Move Help modal creation into Template Haskell - Use lenses for nested data? +- Split up Draw/Modal code into more logical chunks +- Share code between tasks and sub-tasks lists? ## Bugs @@ -25,6 +27,7 @@ - Sub-task count not visible on last item in a list longer than the vertical height - Pressing Enter on empty list shows an subtasks box with an error - Empty tasks - i.e. just a space - don't show up +- No obvious way to know if there are more items in a list off-screen ## To Do From f9e0ed4b8db173a8803b896e157a4c576b25453a Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Mon, 19 Feb 2018 10:26:25 +0000 Subject: [PATCH 19/22] feat (IO.Markdown): added warning if file could not be fully parsed --- app/Main.hs | 8 +++++++- roadmap.md | 2 +- src/IO/Markdown.hs | 38 +++++++++++++++++++++++++------------- src/IO/Taskell.hs | 2 +- 4 files changed, 34 insertions(+), 16 deletions(-) diff --git a/app/Main.hs b/app/Main.hs index 04a81dd8..36747234 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -11,4 +11,10 @@ main :: IO () main = do config <- setup (exists, path) <- T.exists config - when exists $ create path <$> T.readFile config path >>= go config + + when exists $ do + content <- T.readFile config path + + case content of + Right lists -> go config $ create path lists + Left err -> putStrLn $ path ++ ": " ++ err diff --git a/roadmap.md b/roadmap.md index 3318d8c1..e278539a 100644 --- a/roadmap.md +++ b/roadmap.md @@ -45,7 +45,6 @@ ## In Progress - One bad config line stops all config from working - needs to merge with defaultConfig -- Display a warning if any line of the file could not be parsed - otherwise could lead to data loss ## Done @@ -139,3 +138,4 @@ * ~Change sub-list: e.g. from " *" to "-"~ - Feels sluggish in sub-task view - cache main view? - Leaving search only refreshes current list +- Display a warning if any line of the file could not be parsed - otherwise could lead to data loss diff --git a/src/IO/Markdown.hs b/src/IO/Markdown.hs index 1b44418e..22cde469 100644 --- a/src/IO/Markdown.hs +++ b/src/IO/Markdown.hs @@ -5,7 +5,8 @@ module IO.Markdown ( trimListItem ) where -import Data.Text (Text, drop, append, null, lines, isPrefixOf, strip, dropAround, snoc) +import Data.Text as T (Text, drop, append, null, lines, isPrefixOf, strip, dropAround, snoc) +import Data.List (intercalate) import Data.Text.Encoding (encodeUtf8, decodeUtf8With) import Data.Taskell.Lists (Lists, newList, appendToLast) @@ -20,16 +21,16 @@ import IO.Config (Config, MarkdownConfig, markdown, titleOutput, taskOutput, sub -- parse code trimListItem :: Text -> Text -trimListItem = strip . Data.Text.drop 1 +trimListItem = strip . T.drop 1 trimTitle :: Text -> Text -trimTitle = strip . Data.Text.drop 2 +trimTitle = strip . T.drop 2 trimTask :: Text -> Task trimTask = new . trimListItem trimTilde :: Text -> Text -trimTilde = strip . Data.Text.dropAround (== '~') +trimTilde = strip . T.dropAround (== '~') addSubItem :: Text -> Lists -> Lists addSubItem t ls = adjust' updateList i ls @@ -39,21 +40,32 @@ addSubItem t ls = adjust' updateList i ls updateList l = updateFn j (addSubTask st) l where j = count l - 1 -start :: MarkdownConfig -> Lists -> Text -> Lists -start config ls s | titleOutput config `snoc` ' ' `isPrefixOf` s = newList (trimTitle s) ls - | taskOutput config `snoc` ' ' `isPrefixOf` s = appendToLast (trimTask s) ls - | subtaskOutput config `snoc` ' ' `isPrefixOf` s = addSubItem (trimListItem $ strip s) ls - | otherwise = ls +start :: MarkdownConfig -> (Lists, [Int]) -> (Text, Int) -> (Lists, [Int]) +start config (ls, errs) (s, li) + | titleOutput config `snoc` ' ' `isPrefixOf` s = (newList (trimTitle s) ls, errs) + | taskOutput config `snoc` ' ' `isPrefixOf` s = (appendToLast (trimTask s) ls, errs) + | subtaskOutput config `snoc` ' ' `isPrefixOf` s = (addSubItem (trimListItem $ strip s) ls, errs) + | not (T.null (strip s)) = (ls, errs ++ [li]) + | otherwise = (ls, errs) decodeError :: String -> Maybe Word8 -> Maybe Char decodeError _ _ = Just '\65533' -parse :: Config -> ByteString -> Lists -parse config s = foldl' (start (markdown config)) empty $ Data.Text.lines $ decodeUtf8With decodeError s +parse :: Config -> ByteString -> Either String Lists +parse config s = do + let lns = T.lines $ decodeUtf8With decodeError s + let fn = start (markdown config) + let acc = (empty, []) + let (lists, errs) = foldl' fn acc $ zip lns [1..] + + if Prelude.null errs + then Right lists + else Left $ "could not parse line(s) " ++ intercalate ", " (show <$> errs) + -- stringify code join :: Text -> [Text] -> Text -join = foldl' Data.Text.append +join = foldl' T.append subTaskToString :: MarkdownConfig -> Text -> SubTask -> Text subTaskToString config t st = join t [ @@ -77,7 +89,7 @@ taskToString config s t = join s [ listToString :: MarkdownConfig -> Text -> List -> Text listToString config s l = join s [ - if Data.Text.null s then "" else "\n" + if T.null s then "" else "\n" , titleOutput config , " " , title l diff --git a/src/IO/Taskell.hs b/src/IO/Taskell.hs index 37e4663b..5b19a5de 100644 --- a/src/IO/Taskell.hs +++ b/src/IO/Taskell.hs @@ -41,7 +41,7 @@ writeFile :: Config -> Lists -> FilePath -> IO () writeFile config tasks path = void (BS.writeFile path $ stringify config tasks) -- reads json file -readFile :: Config -> FilePath -> IO Lists +readFile :: Config -> FilePath -> IO (Either String Lists) readFile config path = do content <- BS.readFile path return $ parse config content From 8fead832770c05d5a9242f9775f7eb9500c2376f Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Mon, 19 Feb 2018 10:36:41 +0000 Subject: [PATCH 20/22] refactor (UI.Draw): simplified code for sub-task counter --- src/UI/Draw.hs | 17 ++++++----------- 1 file changed, 6 insertions(+), 11 deletions(-) diff --git a/src/UI/Draw.hs b/src/UI/Draw.hs index adc4d42e..b420906e 100644 --- a/src/UI/Draw.hs +++ b/src/UI/Draw.hs @@ -7,7 +7,7 @@ module UI.Draw ( import Events.State (lists, current, mode, normalise) import Events.State.Types (State, Mode(..), InsertMode(..), Pointer, ModalType(..), SubTasksMode(..)) import Brick -import Data.Text as T (Text, length, pack, concat, append, empty) +import Data.Text as T (Text, length, pack, concat, append) import Data.Taskell.List (List, tasks, title) import Data.Taskell.Task (Task, description, hasSubTasks, countSubTasks, countCompleteSubTasks) import Data.Taskell.Text (wrap) @@ -33,21 +33,16 @@ addCursor li ti d = showCursor name (Location (h, v)) box :: [Text] -> Widget ResourceName box d = padBottom (Pad 1) . vBox $ txt <$> d -subTaskCount :: Task -> Text -subTaskCount t | hasSubTasks t = T.concat [ - "[", - pack . show $ countCompleteSubTasks t, - "/", - pack . show $ countSubTasks t, - "]" - ] - | otherwise = empty +subTaskCount :: Task -> Widget ResourceName +subTaskCount t + | hasSubTasks t = str $ Prelude.concat ["[", show $ countCompleteSubTasks t, "/", show $ countSubTasks t, "]"] + | otherwise = emptyWidget renderTask :: LayoutConfig -> Pointer -> Int -> Int -> Task -> Widget ResourceName renderTask layout p li ti t = cached (RNTask (li, ti)) . padBottom (Pad 1) - . (<=> (withAttr disabledAttr $ txt after)) + . (<=> withAttr disabledAttr after) . (if (li, ti) == p then withAttr taskCurrentAttr . visible else withAttr taskAttr) . addCursor li ti d . vBox $ txt <$> d From e5a42e057834ac94437eee3170c68c60c54a386d Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Mon, 19 Feb 2018 10:42:53 +0000 Subject: [PATCH 21/22] refactor (UI.Modal): simplified modal rendering --- src/UI/Modal.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/UI/Modal.hs b/src/UI/Modal.hs index 06a6fe3c..e2f5eb11 100644 --- a/src/UI/Modal.hs +++ b/src/UI/Modal.hs @@ -78,12 +78,12 @@ st' state width = do st :: State -> Int -> (Text, Widget ResourceName) st state width = fromMaybe ("Error", txt "Oops") $ st' state width -getModal :: State -> ModalType -> [Widget ResourceName] +getModal :: State -> ModalType -> Widget ResourceName getModal s t = case t of - Help -> [surround help] - SubTasks _ _ -> [surround $ st s] + Help -> surround help + SubTasks _ _ -> surround $ st s showModal :: State -> [Widget ResourceName] -> [Widget ResourceName] showModal s view = case mode s of - Modal t -> getModal s t ++ view + Modal t -> getModal s t : view _ -> view From c6b5840caf47f14c4e090fe5d773d1bfba893418 Mon Sep 17 00:00:00 2001 From: Mark Wales Date: Mon, 19 Feb 2018 11:08:38 +0000 Subject: [PATCH 22/22] chore (taskell.cabal): version bump --- taskell.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/taskell.cabal b/taskell.cabal index 02be0d98..3a95ced5 100644 --- a/taskell.cabal +++ b/taskell.cabal @@ -1,5 +1,5 @@ name: taskell -version: 0.11.0.0 +version: 0.11.1.0 -- synopsis: A CLI task manager, written in Haskell -- description: Allows you to create version controlled task lists homepage: https://github.com/smallhadroncollider/taskell#readme