aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Main.hs17
-rw-r--r--WMonad.hs15
2 files changed, 10 insertions, 22 deletions
diff --git a/Main.hs b/Main.hs
index 76fd0d7..3d77aad 100644
--- a/Main.hs
+++ b/Main.hs
@@ -54,7 +54,7 @@ keys = M.fromList $
, (f, m) <- [(view, 0), (tag, shiftMask)]]
--
--- let's get underway
+-- The main entry point
--
main :: IO ()
main = do
@@ -76,14 +76,11 @@ main = do
forM_ ws $ \w -> do
wa <- io $ getWindowAttributes dpy w
when (waMapState wa == waIsViewable) (manage w)
- go dpy
-
+ forever $ handle =<< io (allocaXEvent $ \ev ->
+ nextEvent dpy ev >> getEvent ev)
return ()
where
- -- The main loop
- go dpy = forever $ do
- e <- io $ allocaXEvent $ \ev -> nextEvent dpy ev >> getEvent ev
- handle e
+ forever a = a >> forever a
-- | Grab the keys back
grabKeys :: Display -> Window -> W ()
@@ -168,9 +165,9 @@ reveal w = withDisplay $ \d -> io $ moveWindow d w 0 0
windows :: (WorkSpace -> WorkSpace) -> W ()
windows f = do
modify $ \s -> s { workspace = f (workspace s) }
- ws <- gets workspace
refresh
- trace (show ws) -- log state changes to stderr
+ -- ws <- gets workspace
+ -- trace (show ws) -- log state changes to stderr
-- ---------------------------------------------------------------------
-- Window operations
@@ -200,7 +197,7 @@ focus = windows . W.rotate
kill :: W ()
kill = withDisplay $ \d -> do
ws <- gets workspace
- whenJust (W.peek ws) $ io_ . killClient d
+ whenJust (W.peek ws) $ \w -> io (killClient d w) >> return ()
-- | tag. Move a window to a new workspace
tag :: Int -> W ()
diff --git a/WMonad.hs b/WMonad.hs
index e6e3ae7..322f1f7 100644
--- a/WMonad.hs
+++ b/WMonad.hs
@@ -1,6 +1,6 @@
-----------------------------------------------------------------------------
-- |
--- Module : W.hs
+-- Module : WMonad.hs
-- Copyright : (c) Spencer Janssen 2007
-- License : BSD3-style (see LICENSE)
--
@@ -16,7 +16,7 @@
module WMonad (
W, WorkSpace, WState(..),
- runW, withDisplay, io, io_, forever, spawn, trace, whenJust
+ runW, withDisplay, io, spawn, trace, whenJust
) where
import StackSet (StackSet)
@@ -57,23 +57,14 @@ withDisplay f = gets display >>= f
io :: IO a -> W a
io = liftIO
--- | Lift an IO action into the W monad, discarding any result
-io_ :: IO a -> W ()
-io_ f = liftIO f >> return ()
-
--- | Run an action forever
-forever :: (Monad m) => m a -> m b
-forever a = a >> forever a
-
-- | spawn. Launch an external application
spawn :: String -> W ()
-spawn = io_ . runCommand
+spawn x = io (runCommand x) >> return ()
-- | Run a side effecting action with the current workspace. Like 'when' but
whenJust :: Maybe a -> (a -> W ()) -> W ()
whenJust mg f = maybe (return ()) f mg
-
-- | A 'trace' for the W monad. Logs a string to stderr. The result may
-- be found in your .xsession-errors file
trace :: String -> W ()