Skip to content

Commit

Permalink
fixing edit >>= delete bug
Browse files Browse the repository at this point in the history
  • Loading branch information
aviaviavi committed Oct 30, 2018
1 parent d6f55b4 commit cc1e6c2
Show file tree
Hide file tree
Showing 4 changed files with 42 additions and 36 deletions.
70 changes: 38 additions & 32 deletions app/Server.hs
Original file line number Diff line number Diff line change
@@ -1,45 +1,45 @@
{-# LANGUAGE DeriveAnyClass,
DeriveGeneric,
DataKinds,
OverloadedStrings,
ScopedTypeVariables,
TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}

module Server where

import Config
import Parse
import ToodlesApi
import Types
import Config
import Parse
import ToodlesApi
import Types

import qualified Control.Exception as E
import qualified Control.Exception as E
import Control.Monad
import Control.Monad.IO.Class
import Data.Aeson (FromJSON)
import Data.Aeson (FromJSON)
import Data.Either
import Data.IORef
import Data.List (find, nub)
import Data.List (find, nub)
import Data.Maybe
import Data.String.Utils
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Yaml as Y
import GHC.Generics (Generic)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Yaml as Y
import GHC.Generics (Generic)
import Servant
import System.Console.CmdArgs
import System.Directory
import System.IO.HVFS
import qualified System.IO.Strict as SIO
import qualified System.IO.Strict as SIO
import System.Path
import System.Path.NameManip
import Text.Blaze.Html5 (Html)
import qualified Text.Blaze.Html5 as BZ
import Text.Blaze.Html5 (Html)
import qualified Text.Blaze.Html5 as BZ
import Text.Printf
import Text.Regex.Posix

newtype ToodlesConfig = ToodlesConfig
{ ignore :: [FilePath]
} deriving (Show, Generic, FromJSON)
} deriving (Show, Generic, FromJSON)

app :: ToodlesState -> Application
app s = serve toodlesAPI server
Expand Down Expand Up @@ -166,30 +166,35 @@ deleteTodos (ToodlesState ref _) req = do
refVal@(TodoListResult r _) <- liftIO $ readIORef ref
let toDelete = filter (\t -> entryId t `elem` ids req) r
liftIO $ doUntilNull removeAndAdjust toDelete
let updeatedResults =
refVal
{ todos =
filter (\t -> entryId t `notElem` map entryId toDelete) r
}
_ <- liftIO $ atomicModifyIORef' ref (const (updeatedResults, updeatedResults))
let remainingResults = filter (\t -> entryId t `notElem` map entryId toDelete) r
updatedResults <- return $ foldl (flip adjustLinesAfterDeletionOf) remainingResults toDelete
let remainingResultsRef = refVal { todos = updatedResults }
_ <- liftIO $ atomicModifyIORef' ref (const (remainingResultsRef, remainingResultsRef))
return "{}"

where

doUntilNull :: ([a] -> IO [a]) -> [a] -> IO ()
doUntilNull f xs = do
result <- f xs
if null result
then return ()
else doUntilNull f result

-- If we delete an entry, we need to decrement the line-numbers for the
-- other entries that come later in the file
adjustLinesAfterDeletionOf :: TodoEntry -> [TodoEntry] -> [TodoEntry]
adjustLinesAfterDeletionOf deleted =
map (\remaining ->
if (sourceFile remaining == sourceFile deleted) && (lineNumber remaining > lineNumber deleted)
then remaining { lineNumber = lineNumber remaining - (fromIntegral . length $ body deleted)}
else remaining)

removeAndAdjust :: MonadIO m => [TodoEntry] -> m [TodoEntry]
removeAndAdjust [] = return []
removeAndAdjust (x:xs) = do
removeTodoFromCode x
forM xs $ \t -> return $
if (sourceFile t == sourceFile x) && (lineNumber t > lineNumber x)
then t { lineNumber = lineNumber t - (fromIntegral . length $ body x)}
else t
return $ adjustLinesAfterDeletionOf x xs

where
removeTodoFromCode :: MonadIO m => TodoEntry -> m ()
Expand Down Expand Up @@ -244,7 +249,6 @@ getAllFiles (ToodlesConfig ignoredPaths) basePath =
(do putStrLn $ printf "Running toodles for path: %s" basePath
files <- recurseDir SystemFS basePath
let validFiles = filter isValidFile files
-- TODO(avi|p=3|#cleanup) - make sure it's a file first
mapM
(\f ->
SourceFile f . (map T.pack . lines) <$>
Expand All @@ -256,10 +260,12 @@ getAllFiles (ToodlesConfig ignoredPaths) basePath =
putStrLn ("Error reading " ++ basePath ++ ": " ++ show e) >> return [])

where

isValidFile :: FilePath -> Bool
isValidFile path = fileHasValidExtension && not ignoreFile

where

fileHasValidExtension :: Bool
fileHasValidExtension = any (\ext -> ext `T.isSuffixOf` T.pack path) (map fst fileTypeToComment)

Expand Down
2 changes: 1 addition & 1 deletion package.yaml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: toodles
version: 0.1.0.15
version: 0.1.0.16
github: "aviaviavi/toodles"
license: MIT
author: "Avi Press"
Expand Down
4 changes: 2 additions & 2 deletions toodles.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,10 @@
--
-- see: https://github.com/sol/hpack
--
-- hash: e98824dda65b5d290c9b4c3daf086cb4918385d87f176e675e83a222c6cb1957
-- hash: 1db0fe4af19503b62b329d05d28ee3b9d61e69b6919ca9205e5b0ece19e4faeb

name: toodles
version: 0.1.0.15
version: 0.1.0.16
synopsis: Manage the TODO entries in your code
description: Toodles scrapes your entire repository for TODO entries and organizes them so you can manage your project directly from the code. View, filter, sort, and edit your TODO\'s with an easy to use web application. When you make changes via toodles, the edits will be applied directly the TODO entries in your code. When you\'re done, commit and push your changes to share them with your team!
category: Project Management
Expand Down
2 changes: 1 addition & 1 deletion web/js/app.js
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ $(document).ready(function() {
success: function(data) {
this.todos = data.todos.map(t => {
return {
id: t.id,
id: t.entryId,
assignee: t.assignee,
body: t.body.join("\n"),
lineNumber: t.lineNumber,
Expand Down

0 comments on commit cc1e6c2

Please sign in to comment.