mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Add recompilation forcing, clean up recompile's documentation
This commit is contained in:
parent
6114bb371e
commit
92b4510d7b
2
Main.hs
2
Main.hs
@ -43,7 +43,7 @@ main = do
|
|||||||
--
|
--
|
||||||
buildLaunch :: IO ()
|
buildLaunch :: IO ()
|
||||||
buildLaunch = do
|
buildLaunch = do
|
||||||
recompile
|
recompile False
|
||||||
dir <- fmap (++ "/.xmonad") getHomeDirectory
|
dir <- fmap (++ "/.xmonad") getHomeDirectory
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
executeFile (dir ++ "/xmonad") False args Nothing
|
executeFile (dir ++ "/xmonad") False args Nothing
|
||||||
|
@ -313,25 +313,27 @@ restart mprog resume = do
|
|||||||
catchIO (executeFile prog True args Nothing)
|
catchIO (executeFile prog True args Nothing)
|
||||||
where showWs = show . mapLayout show
|
where showWs = show . mapLayout show
|
||||||
|
|
||||||
-- | Recompile ~\/xmonad\/xmonad.hs.
|
-- | 'recompile force', recompile ~\/.xmonad\/xmonad.hs when any of the
|
||||||
|
-- following apply:
|
||||||
|
-- * force is True
|
||||||
|
-- * the xmonad executable does not exist
|
||||||
|
-- * the xmonad executable is older than xmonad.hs
|
||||||
--
|
--
|
||||||
-- The -i flag is used to restrict recompilation to the xmonad.hs file.
|
-- The -i flag is used to restrict recompilation to the xmonad.hs file only.
|
||||||
--
|
--
|
||||||
-- The file is only recompiled if it is newer than its binary.
|
-- Compilation errors (if any) are logged to ~\/.xmonad\/xmonad.errors. If
|
||||||
|
-- GHC indicates failure with a non-zero exit code, an xmessage containing
|
||||||
|
-- GHC's is spawned.
|
||||||
--
|
--
|
||||||
-- In the event of an error, signalled with GHC returning non-zero exit
|
recompile :: MonadIO m => Bool -> m ()
|
||||||
-- status, any stderr produced by GHC, written to the file xmonad.errors,
|
recompile force = liftIO $ do
|
||||||
-- will be displayed to the user with xmessage
|
|
||||||
--
|
|
||||||
recompile :: MonadIO m => m ()
|
|
||||||
recompile = liftIO $ do
|
|
||||||
dir <- (++ "/.xmonad") <$> getHomeDirectory
|
dir <- (++ "/.xmonad") <$> getHomeDirectory
|
||||||
let bin = dir ++ "/" ++ "xmonad"
|
let bin = dir ++ "/" ++ "xmonad"
|
||||||
err = bin ++ ".errors"
|
err = bin ++ ".errors"
|
||||||
src = bin ++ ".hs"
|
src = bin ++ ".hs"
|
||||||
srcT <- getModTime src
|
srcT <- getModTime src
|
||||||
binT <- getModTime bin
|
binT <- getModTime bin
|
||||||
when (srcT > binT) $ do
|
when (force || srcT > binT) $ 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"] (Just dir)
|
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-no-recomp", "-v0"] (Just dir)
|
||||||
Nothing Nothing Nothing (Just h)
|
Nothing Nothing Nothing (Just h)
|
||||||
|
Loading…
x
Reference in New Issue
Block a user