The recompile function now returns a boolean status instead of ().

This commit is contained in:
nicolas.pouillard 2008-01-05 22:55:00 +00:00
parent 5e61b137fb
commit 9ff105340e
2 changed files with 9 additions and 4 deletions

View File

@ -31,8 +31,8 @@ main = do
case args of case args of
[] -> launch [] -> launch
["--resume", _] -> launch ["--resume", _] -> launch
["--recompile"] -> recompile False ["--recompile"] -> recompile False >> return ()
["--recompile-force"] -> recompile True ["--recompile-force"] -> recompile True >> return ()
["--version"] -> putStrLn "xmonad 0.5" ["--version"] -> putStrLn "xmonad 0.5"
_ -> fail "unrecognized flags" _ -> fail "unrecognized flags"

View File

@ -348,7 +348,9 @@ getXMonadDir = io $ getAppUserDataDirectory "xmonad"
-- GHC indicates failure with a non-zero exit code, an xmessage containing -- GHC indicates failure with a non-zero exit code, an xmessage containing
-- GHC's is spawned. -- GHC's is spawned.
-- --
recompile :: MonadIO m => Bool -> m () -- False is returned if there is compilation errors.
--
recompile :: MonadIO m => Bool -> m Bool
recompile force = io $ do recompile force = io $ do
dir <- getXMonadDir dir <- getXMonadDir
let binn = "xmonad-"++arch++"-"++os let binn = "xmonad-"++arch++"-"++os
@ -358,7 +360,8 @@ recompile force = io $ do
src = base ++ ".hs" src = base ++ ".hs"
srcT <- getModTime src srcT <- getModTime src
binT <- getModTime bin binT <- getModTime bin
when (force || srcT > binT) $ do if (force || srcT > binT)
then do
status <- bracket (openFile err WriteMode) hClose $ \h -> do status <- bracket (openFile err WriteMode) hClose $ \h -> do
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-no-recomp", "-v0", "-o",binn] (Just dir) waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-no-recomp", "-v0", "-o",binn] (Just dir)
Nothing Nothing Nothing (Just h) Nothing Nothing Nothing (Just h)
@ -370,6 +373,8 @@ recompile force = io $ do
["Error detected while loading xmonad configuration file: " ++ src] ["Error detected while loading xmonad configuration file: " ++ src]
++ lines ghcErr ++ ["","Please check the file for errors."] ++ lines ghcErr ++ ["","Please check the file for errors."]
doubleFork $ executeFile "xmessage" True [msg] Nothing doubleFork $ executeFile "xmessage" True [msg] Nothing
return (status == ExitSuccess)
else return True
where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing) where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
-- | Run a side effecting action with the current workspace. Like 'when' but -- | Run a side effecting action with the current workspace. Like 'when' but