summaryrefslogtreecommitdiffstats
path: root/XMonad.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@cse.unsw.edu.au>2007-05-20 09:00:53 +0200
committerDon Stewart <dons@cse.unsw.edu.au>2007-05-20 09:00:53 +0200
commitdd74e94f111873c722ff3cbafa1932d310768a08 (patch)
tree717dc51c42ca4f997bce5009624991c68a5a04f7 /XMonad.hs
parent953d9abb472d4e7a80d79c24a80b81269f294982 (diff)
downloadmetatile-dd74e94f111873c722ff3cbafa1932d310768a08.tar
metatile-dd74e94f111873c722ff3cbafa1932d310768a08.zip
HEADS UP: Rewrite StackSet as a Zipper
In order to give a better account of how focus and master interact, and how each operation affects focus, we reimplement the StackSet type as a two level nested 'Zipper'. To quote Oleg: A Zipper is essentially an `updateable' and yet pure functional cursor into a data structure. Zipper is also a delimited continuation reified as a data structure. That is, we use the Zipper as a cursor which encodes the window which is in focus. Thus our data structure tracks focus correctly by construction! We then get simple, obvious semantics for e.g. insert, in terms of how it affects focus/master. Our transient-messes-with-focus bug evaporates. 'swap' becomes trivial. By moving focus directly into the stackset, we can toss some QC properties about focus handling: it is simply impossible now for focus to go wrong. As a benefit, we get a dozen new QC properties for free, governing how master and focus operate. The encoding of focus in the data type also simplifies the focus handling in Operations: several operations affecting focus are now simply wrappers over StackSet. For the full story, please read the StackSet module, and the QC properties. Finally, we save ~40 lines with the simplified logic in Operations.hs For more info, see the blog post on the implementation, http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/17#xmonad_part1b_zipper darcs-hash:20070520070053-9c5c1-241f7ee7793f5db2b9e33d375965cdc21b26cbd7
Diffstat (limited to 'XMonad.hs')
-rw-r--r--XMonad.hs35
1 files changed, 31 insertions, 4 deletions
diff --git a/XMonad.hs b/XMonad.hs
index 22fce97..b985de8 100644
--- a/XMonad.hs
+++ b/XMonad.hs
@@ -18,7 +18,7 @@
module XMonad (
X, WindowSet, WorkspaceId(..), ScreenId(..), XState(..), XConf(..), Layout(..),
Typeable, Message, SomeMessage(..), fromMessage,
- runX, io, withDisplay, isRoot, spawn, trace, whenJust
+ runX, io, withDisplay, withWorkspace, isRoot, spawn, restart, trace, whenJust, whenX
) where
import StackSet (StackSet)
@@ -28,6 +28,8 @@ import Control.Monad.Reader
import System.IO
import System.Posix.Process (executeFile, forkProcess, getProcessStatus, createSession)
import System.Exit
+import System.Environment
+import System.Directory
import Graphics.X11.Xlib
import Data.Typeable
@@ -53,7 +55,7 @@ data XConf = XConf
, normalBorder :: !Color -- ^ border color of unfocused windows
, focusedBorder :: !Color } -- ^ border color of the focused window
-type WindowSet = StackSet WorkspaceId ScreenId Window
+type WindowSet = StackSet WorkspaceId Window ScreenId
-- | Virtual workspace indicies
newtype WorkspaceId = W Int deriving (Eq,Ord,Show,Enum,Num,Integral,Real)
@@ -85,6 +87,10 @@ runX c st (X a) = runStateT (runReaderT a c) st >> return ()
withDisplay :: (Display -> X ()) -> X ()
withDisplay f = asks display >>= f
+-- | Run a monadic action with the current workspace
+withWorkspace :: (WindowSet -> X a) -> X a
+withWorkspace f = gets workspace >>= f
+
-- | True if the given window is the root window
isRoot :: Window -> X Bool
isRoot w = liftM (w==) (asks theRoot)
@@ -119,12 +125,11 @@ fromMessage :: Message m => SomeMessage -> Maybe m
fromMessage (SomeMessage m) = cast m
-- ---------------------------------------------------------------------
--- Utilities
+-- General utilities
-- | Lift an IO action into the X monad
io :: IO a -> X a
io = liftIO
-{-# INLINE io #-}
-- | spawn. Launch an external application
spawn :: String -> X ()
@@ -136,10 +141,32 @@ spawn x = io $ do
getProcessStatus True False pid
return ()
+-- | Restart xmonad by exec()'ing self. This doesn't save state and xmonad has
+-- to be in PATH for this to work.
+restart :: IO ()
+restart = do
+ prog <- getProgName
+ prog_path <- findExecutable prog
+ case prog_path of
+ Nothing -> return () -- silently fail
+ Just p -> do args <- getArgs
+ executeFile p True args Nothing
+
-- | Run a side effecting action with the current workspace. Like 'when' but
whenJust :: Maybe a -> (a -> X ()) -> X ()
whenJust mg f = maybe (return ()) f mg
+-- | Conditionally run an action, using a X event to decide
+whenX :: X Bool -> X () -> X ()
+whenX a f = a >>= \b -> when b f
+
+-- | Grab the X server (lock it) from the X monad
+-- withServerX :: X () -> X ()
+-- withServerX f = withDisplay $ \dpy -> do
+-- io $ grabServer dpy
+-- f
+-- io $ ungrabServer dpy
+
-- | A 'trace' for the X monad. Logs a string to stderr. The result may
-- be found in your .xsession-errors file
trace :: String -> X ()