[Xmonad] patch: XMonadContrib.DwmPromote: dwm-like promote

Miikka Koskinen arcatan at kapsi.fi
Tue May 1 04:32:24 EDT 2007


Hullo,

I like the way dwm's equivalent to xmonad promote works, so I
implemented dwmpromote. See the patch for details.

-- 
Miikka Koskinen (also known as arcatan)
-------------- next part --------------

New patches:

[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.
] {
addfile ./DwmPromote.hs
hunk ./DwmPromote.hs 1
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonadContrib.DwmPromote
+-- Copyright   :  (c) Miikka Koskinen 2007
+-- License     :  BSD3-style (see LICENSE)
+--
+-- Maintainer  :  arcatan at kapsi.fi
+--
+-----------------------------------------------------------------------------
+--
+-- Dwm-like promote function for xmonad.
+--
+-- Swaps focused window with the master window. If focus is in the
+-- master, swap it with the next window in the stack. Focus stays in the
+-- master.
+--
+-- To use, modify your Config.hs to:
+--
+--      import XMonadContrib.DwmPromote
+--
+-- and add a keybinding or substitute promote with dwmpromote:
+--
+--     , ((modMask,               xK_Return), dwmpromote)
+--
+
+module XMonadContrib.DwmPromote (dwmpromote) where
+
+import XMonad
+import Operations (windows)
+import StackSet hiding (promote)
+import qualified Data.Map as M
+
+dwmpromote :: X ()
+dwmpromote = windows promote
+
+promote :: (Integral i, Ord a) => StackSet i j a -> StackSet i j a
+promote w = maybe w id $ do
+    a <- peek w -- fail if null
+    let stack = index (current w) w
+    let newstack = swap a (next stack a) stack
+    return $ w { stacks = M.insert (current w) newstack (stacks w),
+                 focus = M.insert (current w) (head newstack) (focus w) }
+  where
+    next s a | head s /= a = head s -- focused is not master
+             | length s > 1 = s !! 1
+             | otherwise = a
}

Context:

[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:
283e5ea9923cb6acb59fb25a5416131fbf27d699


More information about the Xmonad mailing list