Skip to content

Commit

Permalink
#23 - Added better echo commands when a source file changes
Browse files Browse the repository at this point in the history
  • Loading branch information
karun012 committed Apr 2, 2015
1 parent 1b24ebe commit 86f019b
Show file tree
Hide file tree
Showing 4 changed files with 31 additions and 17 deletions.
14 changes: 9 additions & 5 deletions src/Arion/EventProcessor.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,7 @@ module Arion.EventProcessor (

import Arion.Types
import Control.Applicative ((<$>))
import Data.List (isSuffixOf)
import Data.List (nub)
import Data.List (find, isSuffixOf, nub)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Filesystem.Path (FilePath)
Expand All @@ -20,16 +19,21 @@ respondToEvent (Modified filePath time) = Just (filePath,time)
respondToEvent (Added filePath time) = Just (filePath,time)
respondToEvent _ = Nothing

processEvent :: M.Map String [TestFile] -> String -> String -> (FilePath, t) -> [Command]
processEvent sourceToTestFileMap sourceFolder testFolder (filePath,_)
processEvent :: M.Map String [TestFile] -> String -> String -> [SourceFile] -> (FilePath, t) -> [Command]
processEvent sourceToTestFileMap sourceFolder testFolder allSources (filePath,_)
| isSuffixOf "hs" encodedFilePath =
let fileType = typeOf encodedFilePath
commandCandidates = case fileType of
Source -> nub . map testFilePath . fromMaybe []
$ M.lookup encodedFilePath sourceToTestFileMap
Test -> [encodedFilePath]
maybeLacksTests = if commandCandidates == [] then [Echo (encodedFilePath ++ " does not have any associated tests...")] else []
in Echo (encodedFilePath ++ " changed") : maybeLacksTests ++
sourceFile = find (\file -> sourceFilePath file == encodedFilePath) allSources
whatChanged = case sourceFile of
Just source -> (Echo $ moduleName source ++ " changed") : [Echo (moduleName source ++ " is associated with these tests")]
_ -> [Echo $ encodedFilePath ++ " changed"]
testFileEchoCommands = if fileType == Test then [] else map Echo commandCandidates
in whatChanged ++ testFileEchoCommands ++ maybeLacksTests ++
map (RunHaskell sourceFolder testFolder ) commandCandidates
| otherwise = []
where encodedFilePath = encodeString filePath
2 changes: 1 addition & 1 deletion src/Arion/Runner.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ startWatching path sourceFolder testFolder manager = do
lock <- newEmptyMVar
inProgress <- newIORef Map.empty
_ <- watchTree manager (fromText $ pack path) (const True)
(eventHandler lock inProgress (processEvent sourceToTestFileMap sourceFolder testFolder) . respondToEvent)
(eventHandler lock inProgress (processEvent sourceToTestFileMap sourceFolder testFolder sourceFiles) . respondToEvent)
forever $ threadDelay maxBound

filePathAndContent :: String -> IO (FilePath, FileContent)
Expand Down
2 changes: 1 addition & 1 deletion src/Arion/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ data TestFile = TestFile {
imports :: [String]
} deriving (Eq, Ord, Show)

data FileType = Source | Test
data FileType = Source | Test deriving (Eq)

typeOf :: String -> FileType
typeOf filePath
Expand Down
30 changes: 20 additions & 10 deletions test/Arion/EventProcessorSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,60 +23,70 @@ spec = do
let sourceToTestFileMap = fromList [(sourceFilePathA, [testFileA, testFileB])]
let modifiedEvent = fromJust . respondToEvent $ Modified "mydir/ModuleASpec.hs" sampleTime

processEvent sourceToTestFileMap "src" "test" modifiedEvent `shouldBe` [Echo "mydir/ModuleASpec.hs changed", RunHaskell "src" "test" "mydir/ModuleASpec.hs"]
processEvent sourceToTestFileMap "src" "test" [] modifiedEvent `shouldBe` [Echo "mydir/ModuleASpec.hs changed", RunHaskell "src" "test" "mydir/ModuleASpec.hs"]
it "responds to a Modified event on a source file by creating commands to run the associated tests" $ do
let sourceFile = SourceFile { sourceFilePath = "src/ModuleA.hs", moduleName = "ModuleA", importedModules = ["Module1", "Another.Module", "Yet.Another.Module"] }
let sourceFilePathA = "src/ModuleA.hs"
let testFileA = TestFile "test/ModuleASpec.hs" ["ModuleA"]
let testFileB = TestFile "test/ModuleBSpec.hs" ["ModuleB"]
let sourceToTestFileMap = fromList [(sourceFilePathA, [testFileA, testFileB])]
let modifiedEvent = fromJust . respondToEvent $
Modified "src/ModuleA.hs" sampleTime

processEvent sourceToTestFileMap "src" "test" modifiedEvent `shouldBe` [Echo "src/ModuleA.hs changed", RunHaskell "src" "test" "test/ModuleASpec.hs",
RunHaskell "src" "test" "test/ModuleBSpec.hs"]
processEvent sourceToTestFileMap "src" "test" [sourceFile] modifiedEvent `shouldBe` [Echo "ModuleA changed",
Echo "ModuleA is associated with these tests",
Echo "test/ModuleASpec.hs",
Echo "test/ModuleBSpec.hs",
RunHaskell "src" "test" "test/ModuleASpec.hs",
RunHaskell "src" "test" "test/ModuleBSpec.hs"]
it "responds to a Added event on a test file by creating commands to run tests" $ do
let sourceFilePathA = "src/ModuleA.hs"
let testFileA = TestFile "test/ModuleASpec.hs" ["ModuleA"]
let testFileB = TestFile "test/ModuleBSpec.hs" ["ModuleB"]
let sourceToTestFileMap = fromList [(sourceFilePathA, [testFileA, testFileB])]
let addedEvent = fromJust . respondToEvent $ Added "mydir/ModuleASpec.hs" sampleTime

processEvent sourceToTestFileMap "src" "test" addedEvent `shouldBe` [Echo "mydir/ModuleASpec.hs changed", RunHaskell "src" "test" "mydir/ModuleASpec.hs"]
processEvent sourceToTestFileMap "src" "test" [] addedEvent `shouldBe` [Echo "mydir/ModuleASpec.hs changed", RunHaskell "src" "test" "mydir/ModuleASpec.hs"]
it "responds to a Added event on a source file by creating commands to run the associated tests" $ do
let sourceFile = SourceFile { sourceFilePath = "src/ModuleA.hs", moduleName = "ModuleA", importedModules = ["Module1", "Another.Module", "Yet.Another.Module"] }
let sourceFilePathA = "src/ModuleA.hs"
let testFileA = TestFile "test/ModuleASpec.hs" ["ModuleA"]
let testFileB = TestFile "test/ModuleBSpec.hs" ["ModuleB"]
let sourceToTestFileMap = fromList [(sourceFilePathA, [testFileA, testFileB])]
let addedEvent = fromJust . respondToEvent $ Added "src/ModuleA.hs" sampleTime

processEvent sourceToTestFileMap "src" "test" addedEvent `shouldBe` [Echo "src/ModuleA.hs changed", RunHaskell "src" "test" "test/ModuleASpec.hs",
RunHaskell "src" "test" "test/ModuleBSpec.hs"]
processEvent sourceToTestFileMap "src" "test" [sourceFile] addedEvent `shouldBe` [Echo "ModuleA changed",
Echo "ModuleA is associated with these tests",
Echo "test/ModuleASpec.hs",
Echo "test/ModuleBSpec.hs",
RunHaskell "src" "test" "test/ModuleASpec.hs",
RunHaskell "src" "test" "test/ModuleBSpec.hs"]
it "ignores non haskell source files" $ do
let sourceFilePathA = "src/ModuleA.hs"
let testFileA = TestFile "test/ModuleASpec.hs" ["ModuleA"]
let testFileB = TestFile "test/ModuleBSpec.hs" ["ModuleB"]
let sourceToTestFileMap = fromList [(sourceFilePathA, [testFileA, testFileB])]
let modifiedEvent = fromJust . respondToEvent $ Modified "mydir/ModuleASpec.hs~" sampleTime

processEvent sourceToTestFileMap "src" "test" modifiedEvent `shouldBe` []
processEvent sourceToTestFileMap "src" "test" [] modifiedEvent `shouldBe` []

let addedEvent = fromJust . respondToEvent $ Added "mydir/ModuleASpec.swp" sampleTime

processEvent sourceToTestFileMap "src" "test" addedEvent `shouldBe` []
processEvent sourceToTestFileMap "src" "test" [] addedEvent `shouldBe` []
it "does not ignore lhs files" $ do
let sourceFilePathA = "src/ModuleA.lhs"
let testFileA = TestFile "test/ModuleASpec.lhs" ["ModuleA"]
let testFileB = TestFile "test/ModuleBSpec.lhs" ["ModuleB"]
let sourceToTestFileMap = fromList [(sourceFilePathA, [testFileA, testFileB])]
let addedEvent = fromJust . respondToEvent $ Added "mydir/ModuleASpec.lhs" sampleTime

processEvent sourceToTestFileMap "src" "test" addedEvent `shouldBe` [Echo "mydir/ModuleASpec.lhs changed", RunHaskell "src" "test" "mydir/ModuleASpec.lhs"]
processEvent sourceToTestFileMap "src" "test" [] addedEvent `shouldBe` [Echo "mydir/ModuleASpec.lhs changed", RunHaskell "src" "test" "mydir/ModuleASpec.lhs"]
it "tells you when a source file does not have any tests" $ do
let sourceFilePathA = "src/ModuleA.hs"
let sourceToTestFileMap = fromList [(sourceFilePathA, [])]
let addedEvent = fromJust . respondToEvent $ Added "src/ModuleA.hs" sampleTime

processEvent sourceToTestFileMap "src" "test" addedEvent `shouldBe` [Echo "src/ModuleA.hs changed", Echo "src/ModuleA.hs does not have any associated tests..."]
processEvent sourceToTestFileMap "src" "test" [] addedEvent `shouldBe` [Echo "src/ModuleA.hs changed", Echo "src/ModuleA.hs does not have any associated tests..."]

sampleTime :: UTCTime
sampleTime = UTCTime (ModifiedJulianDay 2) (secondsToDiffTime 2)

1 comment on commit 86f019b

@karun012
Copy link
Owner Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@mwotton Check this out!

Please sign in to comment.