summaryrefslogtreecommitdiffstats
path: root/XMonad/Core.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-19 04:22:55 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-19 04:22:55 +0100
commitda0fe17954c46860c020e5eccb9a1a49cd473412 (patch)
tree5ad99683d8a7f021c8af1e914a79fc5dabeac017 /XMonad/Core.hs
parenta7ba4c32e704a2243bb3d71c8cc95d3488b12f31 (diff)
downloadmetatile-da0fe17954c46860c020e5eccb9a1a49cd473412.tar
metatile-da0fe17954c46860c020e5eccb9a1a49cd473412.zip
Refactor recompile
darcs-hash:20071119032255-a5988-cf1987eab9261b9d8787ab6d36b6437842cf014e
Diffstat (limited to 'XMonad/Core.hs')
-rw-r--r--XMonad/Core.hs31
1 files changed, 15 insertions, 16 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index 4990311..8e89ac1 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -314,22 +314,21 @@ recompile = liftIO $ do
let bin = dir ++ "/" ++ "xmonad"
err = bin ++ ".errors"
src = bin ++ ".hs"
- yes <- doesFileExist src
- when yes $ do
- srcT <- getModificationTime src
- binT <- catch (getModificationTime bin) (const $ return srcT) -- needs recompiling
- when (srcT >= binT) $ do
- status <- bracket (openFile err WriteMode) hClose $ \h -> do
- waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-v0"] (Just dir)
- Nothing Nothing Nothing (Just h)
-
- -- now, if it fails, run xmessage to let the user know:
- when (status /= ExitSuccess) $ do
- ghcErr <- readFile err
- let msg = unlines $
- ["Error detected while loading xmonad configuration file: " ++ src]
- ++ lines ghcErr ++ ["","Please check the file for errors."]
- doubleFork $ executeFile "xmessage" True [msg] Nothing
+ srcT <- getModTime src
+ binT <- getModTime bin
+ when (srcT > binT) $ do
+ status <- bracket (openFile err WriteMode) hClose $ \h -> do
+ waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-v0"] (Just dir)
+ Nothing Nothing Nothing (Just h)
+
+ -- now, if it fails, run xmessage to let the user know:
+ when (status /= ExitSuccess) $ do
+ ghcErr <- readFile err
+ let msg = unlines $
+ ["Error detected while loading xmonad configuration file: " ++ src]
+ ++ lines ghcErr ++ ["","Please check the file for errors."]
+ doubleFork $ executeFile "xmessage" True [msg] Nothing
+ where getModTime f = catch (fmap Just $ getModificationTime f) (const $ return Nothing)
-- | Run a side effecting action with the current workspace. Like 'when' but
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()