From dcf53fbaf601c38a145c3f3f3d2b04843c0c3bf9 Mon Sep 17 00:00:00 2001
From: Lukas Mai <l.mai@web.de>
Date: Thu, 8 Nov 2007 23:09:33 +0000
Subject: [PATCH] refactor main, add "recompile" to XMonad.Core

---
 Main.hs        |  6 ++----
 XMonad/Core.hs | 15 ++++++++++++++-
 2 files changed, 16 insertions(+), 5 deletions(-)

diff --git a/Main.hs b/Main.hs
index 56df3cd..03b2d69 100644
--- a/Main.hs
+++ b/Main.hs
@@ -16,10 +16,10 @@ module Main (main) where
 
 import XMonad.Main
 import XMonad.Config
+import XMonad.Core (recompile)
 
 import Control.Exception (handle)
 import System.IO
-import System.Process
 import System.Directory
 import System.Environment
 import System.Posix.Process (executeFile)
@@ -43,10 +43,8 @@ main = do
 --
 buildLaunch ::  IO ()
 buildLaunch = do
+    recompile
     dir <- fmap (++ "/.xmonad") getHomeDirectory
-    pid <- runProcess "ghc" ["--make", "xmonad.hs"] (Just dir)
-        Nothing Nothing Nothing Nothing
-    waitForProcess pid
     args <- getArgs
     executeFile (dir ++ "/xmonad") False args Nothing
     return ()
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