As you can see I sent patch to XMonad.Actions.FocusNth last week. There
were some stupid mistakes I didn't notice although these were big
mistakes. Now I hope they've gone. So it's my second attempt. Please
provide me with information about "state of approving".
Besides, I've got a question which appeared while I was fixing mistakes
in this patch. The best way to understand it is simply to simulate it by
yourself. So choose a workspace with fullscreen layout. Execute one full
screen program. Then one floating. Then full screen again. It would be
better if you could tell both full screen apps apart easily. Now focus
the application you ran most recent (let's call it A). Then focus down
to the floating application. Now this floating application is really in
the focus but application A has gone from the background. Instead
application you ran the first is in the background. So my question is
about whether it is possible to by-pass this behavior.
Thanks.
Sun Oct 19 17:03:30 EEST 2008 Aleksey Artamonov
* FocusNth improvements fixed
There were some stupid mistakes in the previous version I sent. The
main idea has not changed. This patch provides a way of altering
switching order of FocusNth.
New patches:
[FocusNth improvements fixed
Aleksey Artamonov **20081019140330
There were some stupid mistakes in the previous version I sent. The
main idea has not changed. This patch provides a way of altering
switching order of FocusNth.
] {
hunk ./XMonad/Actions/FocusNth.hs 17
- focusNth) where
+ focusNth,
+ focusNthExt
+ ) where
hunk ./XMonad/Actions/FocusNth.hs 21
-import XMonad.StackSet
+import XMonad.StackSet hiding (filter)
hunk ./XMonad/Actions/FocusNth.hs 35
+-- Sometimes it is really convenient to alter the order
+-- of windows' switching or to omit some of the windows
+-- at all. To fulfill this 'focusNthExt' should be used.
+-- The following code switches to the floating windows
+-- only after all the others (uses XMonad.Util.EZConfig):
+--
+-- > -- mod-[F1 .. F9]
+-- > ++
+-- > [ ("M-", do
+-- > state <- get
+-- > floating <- return $ W.floating (windowset state)
+-- > focusNthExt (\x -> let (a, b) = partition (not . (flip M.member) floating) x in a ++ b)
+-- > i)
+-- > | (k, i) <- zip (map show [1..]) [0..8]
+-- > ]
+--
hunk ./XMonad/Actions/FocusNth.hs 56
-focusNth = windows . modify' . focusNth'
-
-focusNth' :: Int -> Stack a -> Stack a
-focusNth' n s@(Stack _ ls rs) | (n < 0) || (n > length(ls) + length(rs)) = s
- | otherwise = listToStack n (integrate s)
+focusNth = focusNthExt (\x -> x)
hunk ./XMonad/Actions/FocusNth.hs 58
-listToStack :: Int -> [a] -> Stack a
-listToStack n l = Stack t ls rs
- where
- (t:rs) = drop n l
- ls = reverse (take n l)
+-- | Give focus to the nth window taking into consideration windows' rearranging
+-- function.
+focusNthExt :: ([Window] -> [Window]) -> Int -> X()
+focusNthExt t = windows . modify' . (focusNth' t)
hunk ./XMonad/Actions/FocusNth.hs 63
+focusNth' :: ([Window] -> [Window]) -> Int -> Stack Window -> Stack Window
+focusNth' transform n s =
+ let integrated = integrate s
+ transformed = transform $ integrated
+ matching = length transformed
+ in if (n < 0) || (n >= matching)
+ then s
+ else listToStack n transformed integrated
hunk ./XMonad/Actions/FocusNth.hs 72
+listToStack :: Int -> [Window] -> [Window] -> Stack Window
+listToStack num transformed real = Stack t (reverse rls) rs
+ where
+ t = transformed !! num
+ (rls, _ : rs) = span (/= t) real
}
Context:
[Prompt.hs rename deleteConsecutiveDuplicates
gwern0@gmail.com**20081008205131
That name is really unwieldy and long.
]
[Prompt.hs: have historyCompletion filter dupes
gwern0@gmail.com**20081008204710
Specifically, it calls deleteConsecutiveDuplicates on the end product. uniqSort reverses order in an unfortunate way, so we don't use that.
The use-case is when a user has added the same input many times - as it stands, if the history records 30 'top's or whatever, the completion will show 30 'top' entries! This fixes that.
]
[Prompt.hs: tweak haddocks
gwern0@gmail.com**20081008204649]
[Prompt.hs: mv uniqSort to next to its confreres, and mention the trade-off
gwern0@gmail.com**20081008192645]
[Do not consider XMONAD_TIMER unknown
Joachim Breitner **20081008195643]
[Kill window without focusing it first
Joachim Breitner **20081005002533
This patch requires the patch "add killWindow function" in xmonad.
Before this patch, people would experience “workspace flicker” when closing
a window via EWMH that is not on the current workspace, for example when
quitting pidgin via the panel icon.
]
[let MagnifyLess actually magnify less
daniel@wagner-home.com**20081015153911]
[Depend on X11 >= 1.4.3
Spencer Janssen **20080921055456]
[Actions.Search: add a few search engines
intrigeri@boum.org**20081008104033
Add Debian {package, bug, tracking system} search engines, as well as Google
Images and isohunt.
]
[Implement HiddenNonEmptyWS with HiddenWS and NonEmptyWS
Joachim Breitner **20081006211027
(Just to reduce code duplication)
]
[Add straightforward HiddenWS to WSType
Joachim Breitner **20081006210548
With NonEmptyWS and HiddenNonEmptyWS present, HiddenWS is obviously missing.
]
[Merge emptyLayoutMod into redoLayout
Joachim Breitner **20081005190220
This removes the emptyLayoutMod method from the LayoutModifier class, and
change the Stack parameter to redoLayout to a Maybe Stack one. It also changes
all affected code. This should should be a refactoring without any change in
program behaviour.
]
[SmartBorders even for empty layouts
Joachim Breitner **20081005184426
Fixes: http://code.google.com/p/xmonad/issues/detail?id=223
]
[Paste.hs: improve haddocks
gwern0@gmail.com**20080927150158]
[Paste.hs: fix haddock
gwern0@gmail.com**20080927145238]
[minor explanatory comment
daniel@wagner-home.com**20081003015919]
[XMonad.Layout.HintedGrid: add GridRatio (--no-test because of haddock breakage)
Lukas Mai **20080930141715]
[XMonad.Util.Font: UTF8 -> USE_UTF8
Lukas Mai **20080930140056]
[Paste.hs: implement noModMask suggestion
gwern0@gmail.com**20080926232056]
[fix a divide by zero error in Grid
daniel@wagner-home.com**20080926204148]
[-DUTF8 flag with -DUSE_UTF8
gwern0@gmail.com**20080921154014]
[XSelection.hs: use CPP to compile against utf8-string
gwern0@gmail.com**20080920151615]
[add XMonad.Config.Azerty
Devin Mullins **20080924044946]
[flip GridRatio to match convention (x/y)
Devin Mullins **20080922033354]
[let Grid have a configurable aspect ratio goal
daniel@wagner-home.com**20080922010950]
[Paste.hs: +warning about ASCII limitations
gwern0@gmail.com**20080921155038]
[Paste.hs: shorten comment lines to under 80 columns per sjanssen
gwern0@gmail.com**20080921154950]
[Forgot to enable historyFilter :(
Spencer Janssen **20080921094254]
[Prompt: add configurable history filters
Spencer Janssen **20080921093453]
[Update my config to use 'statusBar'
Spencer Janssen **20080921063513]
[Rename pasteKey functions to sendKey
Spencer Janssen **20080921062016]
[DynamicLog: doc fixes
Spencer Janssen **20080921061314]
[Move XMonad.Util.XPaste to XMonad.Util.Paste
Spencer Janssen **20080921060947]
[statusBar now supplies the action to toggle struts
Spencer Janssen **20080918013858]
[cleanup - use currentTag
Devin Mullins **20080921011159]
[XPaste.hs: improve author info
gwern0@gmail.com**20080920152342]
[+XMonad.Util.XPaste: a module for pasting strings to windows
gwern0@gmail.com**20080920152106]
[UrgencyHook bug fix: cleanupUrgents should clean up reminders, too
Devin Mullins **20080920062117]
[Sketch of XMonad.Config.Monad
Spencer Janssen **20080917081838]
[raiseMaster
seanmce33@gmail.com**20080912184830]
[Add missing space between dzen command and flags
Daniel Neri **20080915131009]
[Big DynamicLog refactor. Added statusBar, improved compositionality for dzen and xmobar
Spencer Janssen **20080913205931
Compatibility notes:
- dzen type change
- xmobar type change
- dynamicLogDzen removed
- dynamicLogXmobar removed
]
[Take maintainership of XMonad.Prompt
Spencer Janssen **20080911230442]
[Overhaul Prompt to use a zipper for history navigation. Fixes issue #216
Spencer Janssen **20080911225940]
[Use the new completion on tab setting
Spencer Janssen **20080911085940]
[Only start to show the completion window with more than one match
Joachim Breitner **20080908110129]
[XPrompt: Add showCompletionOnTab option
Joachim Breitner **20080908105758
This patch partially implements
http://code.google.com/p/xmonad/issues/detail?id=215
It adds a XPConfig option that, if enabled, hides the completion window
until the user presses Tab once. Default behaviour is preserved.
TODO: If Tab causes a unique completion, continue to hide the completion
window.
]
[XMonad.Actions.Plane.planeKeys: function to make easier to configure
Marco Túlio Gontijo e Silva **20080714153601]
[XMonad.Actions.Plane: removed unneeded hiding
Marco Túlio Gontijo e Silva **20080714152631]
[Improvements in documentation
Marco Túlio Gontijo e Silva **20080709002425]
[Fix haddock typos in XMonad.Config.{Desktop,Gnome,Kde}
Spencer Janssen **20080911040808]
[add clearUrgents for your keys
Devin Mullins **20080909055425]
[add reminder functionality to UrgencyHook
Devin Mullins **20080824200548
I'm considering rewriting remindWhen and suppressWhen as UrgencyHookModifiers, so to speak. Bleh.
]
[TAG 0.8
Spencer Janssen **20080905195420]
Patch bundle hash:
c25bdc9fad76dda0fec8dc42650397a3cdf980f5