You are not logged in.

#1 2009-06-26 12:09:51

lswest
Member
From: Munich, Germany
Registered: 2008-06-14
Posts: 456
Website

Xmonad Question on Floating Applications not always on top

Hey,

I'm switching from Awesome to Xmonad (or, trying to at least) since I'm growing tired of trying to keep up with syntax changes with awesome updates (but still waiting for the numlock on + no keybindings bug to be fixed, so I can't disable updates for it entirely).  Everything is going fairly well, and the only issue I think I need to ask about (the rest is documented well, or already answered), is the fact that Xmonad seems to automatically place any floating windows above others.  This is all fine if you move it to it's own screen, but I generally keep Skype open on the active window, and I want it to lose focus while I'm working on other things, without putting everything else into floating mode as well.  I was wondering if it's an issue with my template xmonad.hs (off the wiki page, if I remember correctly, or else from the Xmonad thread on these forums), or if it's a default that can be changed (or can't be changed, for that matter).  Does anyone have it working so that floating windows just float and can be hidding by tiled windows?

This is the template xmonad.hs I'm using (and will be editing properly if I get this issue sorted out):

-- {{{
--        Initially from not4aw3some at deviantart.com
--- }}}

-- {{{ Imports
-- stuff
import XMonad
import qualified XMonad.StackSet as W
import qualified Data.Map as M
import System.Exit
import Graphics.X11.Xlib
import IO (Handle, hPutStrLn) 
 
-- utils
import XMonad.Util.Run (spawnPipe)
import XMonad.Actions.NoBorders
 
-- hooks
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.XPropManage
-- Dialog and menu hooks
import Graphics.X11.Xlib.Extras
import Foreign.C.Types (CLong)
 
-- layouts
import XMonad.Layout.NoBorders
import XMonad.Layout.ResizableTile
import XMonad.Layout.Gaps
import XMonad.Layout.Named
import XMonad.Layout.PerWorkspace
import XMonad.Layout.IM
import XMonad.Layout.Grid
import Data.Ratio((%))
-- }}}
-------------------------------------------------------------------------------
-- {{{ Main
main = do
       h <- spawnPipe "xmobar ~/.xmobarrc"
       xmonad $ defaultConfig 
              { workspaces = ["main", "www", "code", "im", "gfx", "vid", "doc", "misc"]
              , modMask = mod1Mask
              , borderWidth = 1
              , normalBorderColor = "#5a5a5a"
              , focusedBorderColor = "#daff30"
              , terminal = "urxvt -title urxvt"
              , keys = keys'
              , logHook = logHook' h 
              , layoutHook = layoutHook'
              , manageHook = manageHook'
              }
-- }}}
-------------------------------------------------------------------------------
-- {{{ Log Hooks
logHook' :: Handle ->  X ()
logHook' h = dynamicLogWithPP $ customPP { ppOutput = hPutStrLn h }

customPP :: PP
customPP = defaultPP { ppCurrent = xmobarColor "#daff30" "#000000" . wrap "[" "]"
                     , ppTitle =  shorten 80
                     , ppSep =  "<fc=#daff30> | </fc>"
                     , ppHiddenNoWindows = xmobarColor "#777777" ""
                     , ppUrgent = xmobarColor "#AFAFAF" "#333333" . wrap "*" "*"
                     }
-- }}}
-------------------------------------------------------------------------------
-- {{{ Layout hooks
layoutHook' = customLayout
customLayout =  avoidStruts $ onWorkspace "im" im $ smartBorders tiled ||| smartBorders (Mirror tiled) ||| im ||| noBorders Full

-- [[old (made gap for bottom)
-- customLayout = gaps [(D,16)] $ avoidStruts $ onWorkspace "im" im $ smartBorders tiled ||| smartBorders (Mirror tiled) ||| im ||| noBorders Full
-- ]]end

  where
    tiled = named "[]=" $ ResizableTall 1 (2/100) (1/2) [] --"Tiled"
    im = named "InstantMessenger" $ withIM (12/50) (Role "buddy_list") Grid
-- }}}
-------------------------------------------------------------------------------
-- {{{ Dialog and menu hooks
getProp :: Atom -> Window -> X (Maybe [CLong])
getProp a w = withDisplay $ \dpy -> io $ getWindowProperty32 dpy a w

checkAtom name value = ask >>= \w -> liftX $ do
                a <- getAtom name
                val <- getAtom value
                mbr <- getProp a w
                case mbr of
                  Just [r] -> return $ elem (fromIntegral r) [val]
                  _ -> return False 

checkDialog = checkAtom "_NET_WM_WINDOW_TYPE" "_NET_WM_WINDOW_TYPE_DIALOG"
checkMenu = checkAtom "_NET_WM_WINDOW_TYPE" "_NET_WM_WINDOW_TYPE_MENU"

manageMenus = checkMenu --> doFloat
manageDialogs = checkDialog --> doFloat
-- }}}
-------------------------------------------------------------------------------
-- {{{ Manage Hooks
myManageHook :: ManageHook
myManageHook = composeAll . concat $
    [ [ className       =? c                 --> doFloat | c <- myFloats ]
    , [ title           =? t                 --> doFloat | t <- myOtherFloats ]
    , [ resource        =? r                 --> doIgnore | r <- myIgnores ]
  --  , [ (className =? "URxvt" <&&> title =? "urxvt") --> doF (W.shift "1:main")]
    , [ className       =? "Gran Paradiso"         --> doF (W.shift "www") ]
    , [ className       =? "Firefox"         --> doF (W.shift "www") ]
--    , [ className       =? "Gimp"            --> doF (W.shift "etc") ]
--    , [ className       =? "Gvim"            --> doF (W.shift "code") ]
    , [ className       =? "OpenOffice.org 3.0" --> doF (W.shift "doc") ]
    , [ className       =? "Abiword"                     --> doF (W.shift "doc") ]
    , [ className       =? "Pidgin"          --> doF (W.shift "im") ]
    ]
    where
        myIgnores       = ["stalonetray"]
        myFloats        = []
        myOtherFloats   = ["alsamixer", "Настройки Firefox", "Загрузки", "Дополнения", "Clear Private Data", "Download; Gran Paradiso", "urxvt-float"]

manageHook' :: ManageHook
manageHook' = manageHook defaultConfig <+> manageDocks <+> manageMenus <+> manageDialogs <+> myManageHook
-- }}}
-------------------------------------------------------------------------------
-- {{{ Keys/Button bindings
keys' :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
keys' conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
    -- launching and killing programs
    [ ((modMask,               xK_Return     ), spawn $ XMonad.terminal conf)
    , ((modMask,               xK_p     ), spawn "dmenu_run -fn \"-*-terminus-medium-r-normal-*-12-*-*-*-*-*-*-*\" -nb \"#daff30\" -nf \"#888888\" -sb \"#2A2A2A\" -sf \"#daff30\"")
    , ((modMask .|. shiftMask, xK_f     ), spawn "firefox")
    , ((modMask .|. shiftMask, xK_c     ), kill)
 
    -- layouts
    , ((modMask,               xK_space ), sendMessage NextLayout)
    , ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
    , ((modMask,               xK_b     ), sendMessage ToggleStruts)
 
    -- floating layer stuff
    , ((modMask,               xK_t     ), withFocused $ windows . W.sink)
 
    -- refresh
    , ((modMask,               xK_n     ), refresh)
    , ((modMask .|. shiftMask, xK_w     ), withFocused toggleBorder)
 
    -- focus
    , ((modMask,               xK_Tab   ), windows W.focusDown)
    , ((modMask,               xK_j     ), windows W.focusDown)
    , ((modMask,               xK_k     ), windows W.focusUp)
    , ((modMask,               xK_m     ), windows W.focusMaster)
 
    -- swapping
    , ((modMask .|. shiftMask, xK_Return), windows W.swapMaster)
    , ((modMask .|. shiftMask, xK_j     ), windows W.swapDown  )
    , ((modMask .|. shiftMask, xK_k     ), windows W.swapUp    )
 
    -- increase or decrease number of windows in the master area
    , ((modMask .|. controlMask, xK_h     ), sendMessage (IncMasterN 1))
    , ((modMask .|. controlMask, xK_l     ), sendMessage (IncMasterN (-1)))
 
    -- resizing
    , ((modMask,               xK_h     ), sendMessage Shrink)
    , ((modMask,               xK_l     ), sendMessage Expand)
    , ((modMask .|. shiftMask, xK_h     ), sendMessage MirrorShrink)
    , ((modMask .|. shiftMask, xK_l     ), sendMessage MirrorExpand)
 
    -- quit, or restart
    , ((modMask .|. shiftMask, xK_q     ), io (exitWith ExitSuccess))
    , ((modMask              , xK_q     ), restart "xmonad" True)
    ]
    ++
    -- mod-[1..9] %! Switch to workspace N
    -- mod-shift-[1..9] %! Move client to workspace N
    [((m .|. modMask, k), windows $ f i)
        | (i, k) <- zip (XMonad.workspaces conf) [xK_F1 .. xK_F9]
        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
-- }}}

Thanks in advance,
Lswest

Last edited by lswest (2009-06-26 12:10:43)


Lswest <- the first letter of my username is a lowercase "L".
"...the Linux philosophy is "laugh in the face of danger". Oops. Wrong one. "Do it yourself". That's it." - Linus Torvalds

Offline

#2 2009-07-08 04:02:26

vogt
Member
From: Toronto, Canada
Registered: 2006-11-25
Posts: 389

Re: Xmonad Question on Floating Applications not always on top

The floating layer is in front of the tiled layer, this is not configurable afaik.

You can probably get the same effects as you want by keeping skype on another workspace. If you run the darcs version (there are aur pkgbuilds), I suspect that XMonad.Util.NamedScratchpad could make it convenient to bring skype up, and dismiss it.

Offline

#3 2009-07-08 09:46:02

lswest
Member
From: Munich, Germany
Registered: 2008-06-14
Posts: 456
Website

Re: Xmonad Question on Floating Applications not always on top

Thanks for the response, but I have worked out the kinks in Awesome, since it offers me the behaviour I want out of the box, and i'll just have to deal with changing syntax.  If I ever give xmonad another go, I'll give your suggestion a shot.


Lswest <- the first letter of my username is a lowercase "L".
"...the Linux philosophy is "laugh in the face of danger". Oops. Wrong one. "Do it yourself". That's it." - Linus Torvalds

Offline

#4 2009-07-08 16:07:53

brenix
Member
From: California
Registered: 2008-03-05
Posts: 185

Re: Xmonad Question on Floating Applications not always on top

I'm not sure if this is the same issue, but I have a problem where new windows appear behind/below the current window. I've found a solution on the xmonad documentation, but it doesnt seem to do anything...

Offline

#5 2009-07-08 16:12:01

lswest
Member
From: Munich, Germany
Registered: 2008-06-14
Posts: 456
Website

Re: Xmonad Question on Floating Applications not always on top

brenix wrote:

I'm not sure if this is the same issue, but I have a problem where new windows appear behind/below the current window. I've found a solution on the xmonad documentation, but it doesnt seem to do anything...

Well, I think it would be under the same behaviour, depending on the layout you're using when that happens.  If you're using IM, floating windows (I believe) appear below the others.  Besides that, it's probably not the same issue and you should start a new thread (using a descriptive title describing the issue) (to ensure that people who may have a solution will read the thread, chances are if the title makes someone seem like they can't answer it, they won't always read it), and/or search the forums for anything similar.

Last edited by lswest (2009-07-08 16:22:33)


Lswest <- the first letter of my username is a lowercase "L".
"...the Linux philosophy is "laugh in the face of danger". Oops. Wrong one. "Do it yourself". That's it." - Linus Torvalds

Offline

Board footer

Powered by FluxBB