mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
refactor main, add "recompile" to XMonad.Core
This commit is contained in:
parent
833e37da9c
commit
dcf53fbaf6
6
Main.hs
6
Main.hs
@ -16,10 +16,10 @@ module Main (main) where
|
|||||||
|
|
||||||
import XMonad.Main
|
import XMonad.Main
|
||||||
import XMonad.Config
|
import XMonad.Config
|
||||||
|
import XMonad.Core (recompile)
|
||||||
|
|
||||||
import Control.Exception (handle)
|
import Control.Exception (handle)
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.Process
|
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import System.Posix.Process (executeFile)
|
import System.Posix.Process (executeFile)
|
||||||
@ -43,10 +43,8 @@ main = do
|
|||||||
--
|
--
|
||||||
buildLaunch :: IO ()
|
buildLaunch :: IO ()
|
||||||
buildLaunch = do
|
buildLaunch = do
|
||||||
|
recompile
|
||||||
dir <- fmap (++ "/.xmonad") getHomeDirectory
|
dir <- fmap (++ "/.xmonad") getHomeDirectory
|
||||||
pid <- runProcess "ghc" ["--make", "xmonad.hs"] (Just dir)
|
|
||||||
Nothing Nothing Nothing Nothing
|
|
||||||
waitForProcess pid
|
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
executeFile (dir ++ "/xmonad") False args Nothing
|
executeFile (dir ++ "/xmonad") False args Nothing
|
||||||
return ()
|
return ()
|
||||||
|
@ -20,7 +20,7 @@
|
|||||||
|
|
||||||
module XMonad.Core (
|
module XMonad.Core (
|
||||||
X, WindowSet, WindowSpace, WorkspaceId, ScreenId(..), ScreenDetail(..), XState(..), XConf(..), XConfig(..), LayoutClass(..), Layout(..), readsLayout, Typeable, Message, SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
|
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
|
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW
|
||||||
) where
|
) where
|
||||||
|
|
||||||
@ -32,6 +32,8 @@ import Control.Monad.State
|
|||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.Posix.Process (executeFile, forkProcess, getProcessStatus, createSession)
|
import System.Posix.Process (executeFile, forkProcess, getProcessStatus, createSession)
|
||||||
|
import System.Process
|
||||||
|
import System.Directory
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import Graphics.X11.Xlib
|
import Graphics.X11.Xlib
|
||||||
@ -281,6 +283,17 @@ 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.
|
||||||
|
--
|
||||||
|
-- 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
|
-- | Run a side effecting action with the current workspace. Like 'when' but
|
||||||
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
|
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
|
||||||
whenJust mg f = maybe (return ()) f mg
|
whenJust mg f = maybe (return ()) f mg
|
||||||
|
Loading…
x
Reference in New Issue
Block a user