[Xmonad] patch: FindEmptyWorkspace (+ make DwmPromote compile)

Miikka Koskinen arcatan at kapsi.fi
Tue May 15 11:02:22 EDT 2007


On Mon, May 14, 2007 at 07:42:29AM -0700, David Roundy wrote:
> Sounds good, but I don't see the patch!

Hmmph, I'm pretty sure I attached them. Well, once again, with more
feeling!

-- 
Miikka Koskinen
-------------- next part --------------

New patches:

[XMonadContrib.FindEmptyWorkspace
Miikka Koskinen <arcatan at kapsi.fi>**20070513184338
 
 With this module you can find empty workspaces, view them and tag windows to
 them.
] {
addfile ./FindEmptyWorkspace.hs
hunk ./FindEmptyWorkspace.hs 1
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonadContrib.FindEmptyWorkspace
+-- Copyright   :  (c) Miikka Koskinen 2007
+-- License     :  BSD3-style (see LICENSE)
+--
+-- Maintainer  :  arcatan at kapsi.fi
+--
+-----------------------------------------------------------------------------
+--
+-- Find an empty workspace in xmonad.
+--
+-- To use, modify your Config.hs to:
+--
+--     import XMonadContrib.FindEmptyWorkspace
+--
+-- and add a keybinding:
+--
+--     , ((modMask,                xK_m    ), viewEmptyWorkspace)
+--     , ((modMask .|. shiftMask,  xK_m    ), tagToEmptyWorkspace)
+--
+-- Now you can jump to an empty workspace with mod-n. Mod-shift-n will
+-- tag the current window to an empty workspace and view it.
+--
+
+module XMonadContrib.FindEmptyWorkspace (
+    viewEmptyWorkspace, tagToEmptyWorkspace
+  ) where
+
+import Control.Monad.State
+import qualified Data.Map as M
+
+import XMonad
+import Operations
+import qualified StackSet as W
+
+-- | Find the first empty workspace in a WindowSet. Returns Nothing if
+-- all workspaces are in use.
+findEmptyWorkspace :: WindowSet -> Maybe WorkspaceId
+findEmptyWorkspace = findKey (([],[]) ==) . W.stacks
+
+withEmptyWorkspace :: (WorkspaceId -> X ()) -> X ()
+withEmptyWorkspace f = do
+    ws <- gets workspace
+    whenJust (findEmptyWorkspace ws) f
+
+-- | Find and view an empty workspace. Do nothing if all workspaces are
+-- in use.
+viewEmptyWorkspace :: X ()
+viewEmptyWorkspace = withEmptyWorkspace view
+
+-- | Tag current window to an empty workspace and view it. Do nothing if
+-- all workspaces are in use.
+tagToEmptyWorkspace :: X ()
+tagToEmptyWorkspace = withEmptyWorkspace $ \w -> tag w >> view w
+
+-- Thanks to mauke on #haskell
+findKey :: (a -> Bool) -> M.Map k a -> Maybe k
+findKey f = M.foldWithKey (\k a -> mplus (if f a then Just k else Nothing)) Nothing
}

Context:

[make rotView only consider non-visible workspaces (Xinerama)
Jason Creighton <jcreigh at gmail.com>**20070510012059] 
[fix commend in RotView.
David Roundy <droundy at darcs.net>**20070505185654] 
[switch to Message type for layout messages
Don Stewart <dons at cse.unsw.edu.au>**20070505014332] 
[Fix instructions in Mosaic.
Chris Mears <chris at cmears.id.au>**20070503222345] 
[add Mosaic layout.
David Roundy <droundy at darcs.net>**20070503151024] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070503211700] 
[Make RotView build, and add a brief description.
Chris Mears <chris at cmears.id.au>**20070503104234] 
[comment: Gave URL to xinerama-enabled dmenu patch
Jason Creighton <jcreigh at gmail.com>**20070503053133] 
[Put dmenu in X too
Spencer Janssen <sjanssen at cse.unl.edu>**20070503053727] 
[Add dmenu (thanks jcreigh)
Spencer Janssen <sjanssen at cse.unl.edu>**20070503052225] 
[add RotView module.
David Roundy <droundy at darcs.net>**20070421233838] 
[XMonadContrib.DwmPromote: dwm-like promote
Miikka Koskinen <arcatan at kapsi.fi>**20070501082031
 I like the way dwm's equivalent to xmonad's promote works, so I
 implemented dwmpromote.
] 
[add simple date example
Don Stewart <dons at cse.unsw.edu.au>**20070429064013] 
[more details
Don Stewart <dons at cse.unsw.edu.au>**20070429061426] 
[add readme
Don Stewart <dons at cse.unsw.edu.au>**20070429061329] 
[Initial import of xmonad contributions
Don Stewart <dons at cse.unsw.edu.au>**20070429061150] 
Patch bundle hash:
54475666b60ed44d4b74700a08fc1311626d1294
-------------- next part --------------

New patches:

[make DwmPromote compile
Miikka Koskinen <arcatan at kapsi.fi>**20070503105236] {
hunk ./DwmPromote.hs 40
-    let newstack = swap a (next stack a) stack
-    return $ w { stacks = M.insert (current w) newstack (stacks w),
+        newstack = swap a (next stack a) stack
+    return $ w { stacks = M.adjust (\(f,_) -> (f, newstack)) (current w) (stacks w),
}

[make DwmPromote compile again
Miikka Koskinen <arcatan at kapsi.fi>**20070510154158] {
hunk ./DwmPromote.hs 39
-    let stack = index (current w) w
-        newstack = swap a (next stack a) stack
+    stack <- index (current w) w
+    let newstack = swap a (next stack a) stack
}

[make DwmPromote compile
Miikka Koskinen <arcatan at kapsi.fi>**20070513184254] {
hunk ./DwmPromote.hs 36
-promote :: (Integral i, Ord a) => StackSet i j a -> StackSet i j a
+promote :: (Integral i, Integral j, Ord a) => StackSet i j a -> StackSet i j a
hunk ./DwmPromote.hs 41
-    return $ w { stacks = M.adjust (\(f,_) -> (f, newstack)) (current w) (stacks w),
-                 focus = M.insert (current w) (head newstack) (focus w) }
+    return . raiseFocus (head newstack) $
+        w { stacks = M.adjust (\(f,_) -> (f, newstack)) (current w) (stacks w) }
}

Context:

[make rotView only consider non-visible workspaces (Xinerama)
Jason Creighton <jcreigh at gmail.com>**20070510012059] 
[fix commend in RotView.
David Roundy <droundy at darcs.net>**20070505185654] 
[switch to Message type for layout messages
Don Stewart <dons at cse.unsw.edu.au>**20070505014332] 
[Fix instructions in Mosaic.
Chris Mears <chris at cmears.id.au>**20070503222345] 
[add Mosaic layout.
David Roundy <droundy at darcs.net>**20070503151024] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070503211700] 
[Make RotView build, and add a brief description.
Chris Mears <chris at cmears.id.au>**20070503104234] 
[comment: Gave URL to xinerama-enabled dmenu patch
Jason Creighton <jcreigh at gmail.com>**20070503053133] 
[Put dmenu in X too
Spencer Janssen <sjanssen at cse.unl.edu>**20070503053727] 
[Add dmenu (thanks jcreigh)
Spencer Janssen <sjanssen at cse.unl.edu>**20070503052225] 
[add RotView module.
David Roundy <droundy at darcs.net>**20070421233838] 
[XMonadContrib.DwmPromote: dwm-like promote
Miikka Koskinen <arcatan at kapsi.fi>**20070501082031
 I like the way dwm's equivalent to xmonad's promote works, so I
 implemented dwmpromote.
] 
[add simple date example
Don Stewart <dons at cse.unsw.edu.au>**20070429064013] 
[more details
Don Stewart <dons at cse.unsw.edu.au>**20070429061426] 
[add readme
Don Stewart <dons at cse.unsw.edu.au>**20070429061329] 
[Initial import of xmonad contributions
Don Stewart <dons at cse.unsw.edu.au>**20070429061150] 
Patch bundle hash:
7dc86cb5bcdd9f60ba9d3304cd100f7f07ed905d


More information about the Xmonad mailing list