module Development.Hake.HiddenTools ( runHake , isOldThanSomeOf ) where import System.Directory (createDirectory, doesDirectoryExist, doesFileExist, copyFile, getModificationTime) import System.Process (runProcess, waitForProcess) import System.Exit (ExitCode) import System.Time (ClockTime) import System.IO (openFile, hClose, IOMode(WriteMode)) import Control.Applicative ((<$>), liftA2) import Control.Monad.Utils (whenM, unlessM) import Control.Exception (bracket) maybeGetModificationTime :: FilePath -> IO (Maybe ClockTime) maybeGetModificationTime fn = do ex <- doesFileExist fn if ex then Just <$> getModificationTime fn else return Nothing isOldThanSomeOf :: FilePath -> [FilePath] -> IO Bool isOldThanSomeOf dfn sfns = liftA2 ((myOr .) . map . (<)) (maybeGetModificationTime dfn) (mapM maybeGetModificationTime sfns) where -- for task like "clean" myOr [] = True myOr bs = or bs runHake :: FilePath -> FilePath -> [ FilePath ] -> [ String ] -> IO ExitCode runHake src exe otrs args = do unlessM (doesDirectoryExist "_hake") $ createDirectory "_hake" flip mapM_ otrs $ \fn -> do let dist = "_hake/" ++ basename fn whenM (isOldThanSomeOf dist [ fn ]) $ copyFile fn dist whenM (isOldThanSomeOf ("_hake/" ++ exe ++ ".hs") [ src ]) $ readFile src >>= writeFile ("_hake/" ++ exe ++ ".hs") #ifndef DEBUG bracket (flip openFile WriteMode $ "_hake/" ++ exe ++ ".error") hClose $ \errH -> let mErrH = Just errH in #else let mErrH = Nothing in #endif /* DEBUG */ runProcess "ghc" [ "--make", exe ] (Just "_hake") Nothing Nothing Nothing mErrH >>= waitForProcess runProcess ("_hake/" ++ exe) (if null args then ["default"] else args) Nothing Nothing Nothing Nothing Nothing >>= waitForProcess basename :: FilePath -> FilePath basename = reverse . takeWhile (/='/') . reverse