aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Core.hs
diff options
context:
space:
mode:
authorLukas Mai <l.mai@web.de>2007-11-09 00:09:33 +0100
committerLukas Mai <l.mai@web.de>2007-11-09 00:09:33 +0100
commit189a665cfdd7be7e7b2ef11c1a81a6ca011944da (patch)
treecdbd63c7ae1122453c97d5cd50d654fd300bb89f /XMonad/Core.hs
parent9b6926e72d37d0ee233dd9c30e9521e20c57c77b (diff)
downloadxmonad-189a665cfdd7be7e7b2ef11c1a81a6ca011944da.tar.gz
xmonad-189a665cfdd7be7e7b2ef11c1a81a6ca011944da.tar.xz
xmonad-189a665cfdd7be7e7b2ef11c1a81a6ca011944da.zip
refactor main, add "recompile" to XMonad.Core
darcs-hash:20071108230933-462cf-b1e100cf8f2cecbfef925b870a3fc894fe47513c.gz
Diffstat (limited to 'XMonad/Core.hs')
-rw-r--r--XMonad/Core.hs15
1 files changed, 14 insertions, 1 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index e88082d..8d85afc 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -20,7 +20,7 @@
module XMonad.Core (
X, WindowSet, WindowSpace, WorkspaceId, ScreenId(..), ScreenDetail(..), XState(..), XConf(..), XConfig(..), LayoutClass(..), Layout(..), readsLayout, Typeable, Message, SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
- runX, catchX, userCode, io, catchIO, withDisplay, withWindowSet, isRoot, getAtom, spawn, restart, trace, whenJust, whenX,
+ runX, catchX, userCode, io, catchIO, withDisplay, withWindowSet, isRoot, getAtom, spawn, restart, recompile, trace, whenJust, whenX,
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW
) where
@@ -32,6 +32,8 @@ import Control.Monad.State
import Control.Monad.Reader
import System.IO
import System.Posix.Process (executeFile, forkProcess, getProcessStatus, createSession)
+import System.Process
+import System.Directory
import System.Exit
import System.Environment
import Graphics.X11.Xlib
@@ -281,6 +283,17 @@ restart mprog resume = do
catchIO (executeFile prog True args Nothing)
where showWs = show . mapLayout show
+-- | Recompile ~\/xmonad\/xmonad.hs.
+--
+-- Raises an exception if ghc can't be found.
+recompile :: IO ()
+recompile = do
+ dir <- fmap (++ "/.xmonad") getHomeDirectory
+ pid <- runProcess "ghc" ["--make", "xmonad.hs"] (Just dir)
+ Nothing Nothing Nothing Nothing
+ waitForProcess pid
+ return ()
+
-- | Run a side effecting action with the current workspace. Like 'when' but
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust mg f = maybe (return ()) f mg