[xmonad] Issue 241 in xmonad: 0.8: moving floated window changes
the current tiled master
codesite-noreply at google.com
codesite-noreply at google.com
Tue Nov 25 08:26:15 EST 2008
Status: New
Owner: ----
New issue 241 by lucia.culakova: 0.8: moving floated window changes the
current tiled master
http://code.google.com/p/xmonad/issues/detail?id=241
What steps will reproduce the problem?
1. Create a workspace with 3 tiled and a single float window.
2. Change one of the non-master tiled windows to master.
3. Move the float window around with a mouse.
What is the expected output? What do you see instead?
Nothing happens to the tiled layout, the float window moves. Instead, while
the float window moves, the previous master is swapped back into master
position in the tiled layout.
What version of the product are you using? On what operating system?
This happens in 0.8 from cabal, ghc 6.8.2 on Debian. Downgrading xmonad and
xmonad-contrib to 0.7 fixes the problem.
Please provide any additional information below.
This is my config file: ------------------
import XMonad
import XMonad.Hooks.DynamicLog
import XMonad.Util.EZConfig
import XMonad.Prompt
import XMonad.Prompt.RunOrRaise
import XMonad.Actions.Warp
import qualified XMonad.StackSet as W
import XMonad.Layout.NoBorders
import XMonad.Layout.ShowWName
import XMonad.Layout.PerWorkspace
import XMonad.Layout.ToggleLayouts
import XMonad.Hooks.ManageDocks
main = xmonad conf
modm = modMask conf
ctrlm = controlMask
modctrlm = modm .|. ctrlm
term = "urxvtc"
topRow = [xK_exclam, xK_at, xK_numbersign, xK_dollar, xK_percent,
xK_asciicircum, xK_ampersand, xK_asterisk, xK_parenleft,
xK_parenright]
pointerFollowsFocus :: Rational -> Rational -> X ()
pointerFollowsFocus h v = do
dpy <- asks display
root <- asks theRoot
withFocused $ \w -> do
wa <- io $ getWindowAttributes dpy w
(sameRoot,_,w',_,_,_,_,_) <- io $ queryPointer dpy root
if (sameRoot && w == w') then
return ()
else
io $ warpPointer dpy none w 0 0 0 0
(fraction h (wa_width wa)) (fraction v (wa_height wa))
where fraction x y = floor (x * fromIntegral y)
tiled = Tall 1 delta ratio
where delta = 3/100
ratio = 1/2
manageH = composeAll . concat $
[ [ className =? c --> doFloat | c <- floats],
[ className =? "urxvt" --> doF (W.shift "1:term") ],
[ className =? "Konqueror" --> doF (W.shift "2:web") ],
[ className =? "Emacs" --> doF (W.shift "3:emacs") ]
]
where floats = ["MPlayer", "Gimp", "Xmessage"]
layoutH =
-- show workspace names when switching.
showWName $
-- workspace 1 starts in Full mode and can switch to tiled.
onWorkspace "2:web" (smartBorders $ Full ||| tiled) $
-- start all workspaces in my home directory, with the ability
-- to switch to a new working dir.
-- workspaceDir "~" $
-- navigate directionally rather than with mod-j/k
-- configurableNavigation (navigateColor "#00aa00") $
-- ability to toggle between fullscreen
toggleLayouts (noBorders Full) $
-- toggle vertical/horizontal layout reflection
-- mkToggle (single REFLECTX) $
-- mkToggle (single REFLECTY) $
-- borders automatically disappear for fullscreen windows
avoidStruts $ smartBorders $ (tiled ||| Mirror tiled)
conf = defaultConfig
{ terminal = term
, normalBorderColor = "grey"
, focusedBorderColor = "red"
, workspaces = ["1:term", "2:web", "3:emacs", "4", "5", "6", "7",
"8:trash"]
, modMask = mod4Mask
, logHook = {- grabKeys >> -} pointerFollowsFocus (1/2) (1/2)
, layoutHook = layoutH
, manageHook = manageH
}
`additionalKeys`
(
[ ((modm, xK_p), runOrRaisePrompt defaultXPConfig { position = Top
}),
((modctrlm, xK_Return), spawn term),
((modm, xK_h), windows W.focusUp),
((modm, xK_s), windows W.focusDown),
((modm, xK_w), withFocused $ windows . W.sink),
((modm, xK_t), sendMessage Shrink),
((modm, xK_n), sendMessage Expand),
((modm, xK_b), sendMessage ToggleStruts),
((modctrlm, xK_t), sendMessage NextLayout),
-- ((modctrlm, xK_n), sendMessage PreviousLayout),
((modctrlm, xK_space), sendMessage ToggleLayout),
((modctrlm, xK_s), windows W.swapDown),
((modctrlm, xK_h), windows W.swapUp),
((modctrlm, xK_c), kill)
] ++
[
((m .|. modm, k), windows $ f i)
| (i, k) <- zip (XMonad.workspaces conf) topRow,
(f, m) <- [(W.greedyView, 0), (W.shift, ctrlm)]
] ++
[
((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows
. f))
| (key, sc) <- zip [xK_a, xK_o, xK_e] [0..],
(f, m) <- [(W.view, 0), (W.shift, shiftMask)]
]
)
----------------------------------------
I don't this is due to a contrib module, as this still happens when I cut
down the configuration file considerably.
I recall trying to solve this in #xmonad, but noone has been able to
reproduce, so I am at a loss what's wrong here. But, recompiling xmonad-0.7
against exactly the same system fixes the problem, so I believe this *is* a
xmonad bug...
--
You received this message because you are listed in the owner
or CC fields of this issue, or because you starred this issue.
You may adjust your issue notification preferences at:
http://code.google.com/hosting/settings
More information about the xmonad
mailing list