|
1 | 1 | {-# LANGUAGE ScopedTypeVariables #-} |
2 | 2 | module Main where |
3 | 3 |
|
4 | | -import Control.Exception (IOException, catch) |
5 | | -import Control.Monad (filterM, liftM, unless) |
6 | | -import Data.Map.Lazy (adjust, fromList, insert, toList) |
7 | | -import Data.Maybe (listToMaybe) |
8 | | -import Data.Typeable (typeOf) |
9 | | -import Debug.Trace (traceShow) |
10 | | -import GHC.IO.Exception (IOErrorType (..)) |
11 | | -import System.Directory (doesFileExist, getDirectoryContents, |
12 | | - removeFile, renameFile) |
13 | | -import System.Environment (getArgs, getEnvironment) |
14 | | -import System.Exit (ExitCode (..)) |
15 | | -import System.FilePath (hasExtension, replaceBaseName, |
16 | | - takeBaseName, (</>)) |
17 | | -import System.IO (hPutStrLn, stderr) |
18 | | -import System.IO.Error (ioeGetErrorType) |
19 | | -import System.Process (createProcess, env, shell, waitForProcess) |
| 4 | +import Control.Exception (IOException, catch) |
| 5 | +import Control.Monad (filterM, liftM, unless) |
| 6 | +import qualified Data.ByteString.Lazy as BL |
| 7 | +import Data.Digest.Pure.MD5 (md5) |
| 8 | +import Data.Map.Lazy (adjust, fromList, insert, toList) |
| 9 | +import Data.Maybe (listToMaybe) |
| 10 | +import Data.Typeable (typeOf) |
| 11 | +--import Debug.Trace (traceShow) |
| 12 | +import GHC.IO.Exception (IOErrorType (..)) |
| 13 | +import System.Directory (doesFileExist, getDirectoryContents, |
| 14 | + removeFile, renameFile) |
| 15 | +import System.Environment (getArgs, getEnvironment) |
| 16 | +import System.Exit (ExitCode (..)) |
| 17 | +import System.FilePath (hasExtension, replaceBaseName, |
| 18 | + takeBaseName, (</>)) |
| 19 | +import System.IO (IOMode (..), hGetLine, hPutStrLn, stderr, |
| 20 | + withFile) |
| 21 | +import System.IO.Error (ioeGetErrorType) |
| 22 | +import System.Process (createProcess, env, shell, |
| 23 | + waitForProcess) |
20 | 24 |
|
21 | | -traceShow' arg = traceShow arg arg |
| 25 | +--traceShow' arg = traceShow arg arg |
22 | 26 |
|
23 | 27 | main :: IO () |
24 | 28 | main = mapM_ redo =<< getArgs |
@@ -61,13 +65,14 @@ upToDate :: String -> IO Bool |
61 | 65 | upToDate target = |
62 | 66 | catch |
63 | 67 | (do deps <- getDirectoryContents depDir |
64 | | - (traceShow' . all id) `liftM` mapM depUpToDate deps) |
| 68 | + all id `liftM` mapM depUpToDate deps) |
65 | 69 | (\(e :: IOException) -> return False) |
66 | 70 | where |
67 | 71 | depDir = ".redo" </> target |
68 | 72 | depUpToDate :: FilePath -> IO Bool |
69 | 73 | depUpToDate dep = |
70 | 74 | catch |
71 | | - (do oldMD5 <- traceShow' `liftM` readFile (depDir </> dep) |
72 | | - return False) |
| 75 | + (do oldMD5 <- withFile (depDir </> dep) ReadMode hGetLine |
| 76 | + newMD5 <- md5 `liftM` BL.readFile dep |
| 77 | + return $ oldMD5 == show newMD5) |
73 | 78 | (\(e :: IOException) -> return (ioeGetErrorType e == InappropriateType)) |
0 commit comments