[Haskell-cafe] Behaviour of System.Directory.getModificationTime
Arnaud Bailly
arnaud.oqube at gmail.com
Wed Dec 15 09:29:30 CET 2010
Hello,
I am writing a program which scans a bunch of directories to detect
changes (added, modified, deleted files).
To detect modification, I would like to use getModification, doing
something like the following:
-- |Stores last modified timestamp of the file
-- Yes, I come from Java...
type HashMap = M.Map FilePath ClockTime
data (Show a, Eq a) => Edit a = Mod a
| Add a
| Del a
deriving (Eq,Show)
checkChanges :: [String] -> HashMap -> IO ([Edit FilePath], HashMap)
checkChanges [fs] m = do
addedFilesList <- lsRecursive fs
timestamps <- mapM getModificationTime addedFilesList
let allts = zip addedFilesList timestamps
let ret = (findDeletedFiles allts.updateScannedFiles allts) ([],m)
return ret
-- | Returns an updated map and a list of modified/added/deleted files
updateScannedFiles :: [(FilePath,ClockTime)] -> ([Edit FilePath],
HashMap) -> ([Edit FilePath], HashMap)
updateScannedFiles [] r = r
updateScannedFiles ((path,ts):files) (updates,m) =
case M.lookup path m of
Nothing -> updateScannedFiles files ((Add path:updates), M.insert
path ts m)
Just ts' -> if ts' < ts then
updateScannedFiles files ((Mod path:updates),
M.adjust (const ts) path m)
else
updateScannedFiles files (updates, m)
-- omitting findDeletedFiles which is obvious and works
I got the following test case that fails:
"recursively marks changed files as modified" `for`
do complexFileSetup -- create a small FS tree with 3 files
root <- tempDir
state <- checkChanges [root] M.empty
writeFile (root </> "subdir" </> "cFile.txt") "this is another
toast"
checkChanges [root] (snd state)
>>= (\r -> assertEqual "there should be 1 changed file in 3 files"
1 ((length.modified.fst) r)),
In words: the getModificationTime of the overwritten file appears
identical before and after the write. What am I doing wrong ?
BTW, I checked the content of the file which has been correctly updated.
Thanks for your help
Arnaud
More information about the Haskell-Cafe
mailing list