Question

Since MATE is just a fork of GNOME2, it is apparently possible to replace the window manager with another (i.e. xmonad) using the command: mateconftool-2 -s /desktop/mate/session/required_components/windowmanager xmonad --type string. This works in the sense that XMonad is started when I log into MATE, however, it looks like xmonad is trying to tile the panels or something. One of the panels fills up literally all the space it shouldn't (leaving the top and bottom empty) and the system is totally unusable (time to reboot).

My xmonad.hs:

{-# LANGUAGE OverloadedStrings #-}

import XMonad
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.SetWMName
import Control.Monad
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig
import qualified XMonad.Actions.FlexibleResize as Flex
import XMonad.Hooks.EwmhDesktops

import XMonad.Config.Desktop
import XMonad.Hooks.ManageDocks
import XMonad.Layout.NoBorders
import XMonad.Layout.LayoutHints

import XMonad.Util.Run (safeSpawn)

import System.Environment (getEnvironment)

main = xmonad mateConfig

mateConfig = desktopConfig
            { logHook = spawn "wmname LG3D"
            , manageHook = myManageHook <+> manageHook mateConfig
            , workspaces = ["1", "2", "3", "4", "5", "="]
            , modMask = mod4Mask
            , terminal = "gnome-terminal"
            , startupHook = takeTopFocus >> setWMName "LG3D"
            , handleEventHook = fullscreenEventHook
            --, layoutHook = layoutHints $ avoidStruts (noBorders Full) ||| Mirror (Tall (1 (3/100) (1/2))) 
            , layoutHook = avoidStruts ((noBorders Full) ||| Mirror (Tall 1 (3/100) (1/2)))
         }

         `additionalKeys` [ ((mod4Mask, xK_d), spawn "dmenu_run -fn \"Ubuntu_Mono-13:Normal\" -nb black -nf skyblue -sb skyblue -sf black")
                           ,((mod4Mask, xK_v), spawn "gvim")
                           ,((mod4Mask, xK_x), spawn "gvim ~/.xmonad/xmonad.hs")
                           ,((mod4Mask, xK_p), spawn "gnome-terminal")
                           -- ,((0       , xF86XK_AudioPlay), spawn "echo \"PLAY\" > ~/Desktop/hi")
                            ]

         `additionalMouseBindings` [ ((mod4Mask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
                                    ]


myManageHook = composeAll
    [ className =? "Amarok" --> doShift "="
    , manageDocks
    ]


{--- DBus Stuff-}
-- | Register xmonad with mate. 'dbus-send' must be in the $PATH with which
-- xmonad is started.
--
-- This action reduces a delay on startup only only if you have configured
-- mate-session>=2.26: to start xmonad with a command as such:
--
-- > mateconftool-2 -s /desktop/mate/session/required_components/windowmanager xmonad --type string
mateRegister :: MonadIO m => m ()
mateRegister = io $ do
    x <- lookup "DESKTOP_AUTOSTART_ID" `fmap` getEnvironment
    whenJust x $ \sessionId -> safeSpawn "dbus-send"
            ["--session"
            ,"--print-reply=string"
            ,"--dest=org.mate.SessionManager"
            ,"/org/mate/SessionManager"
            ,"org.mate.SessionManager.RegisterClient"
            ,"string:xmonad"
            ,"string:"++sessionId]




atom_WM_TAKE_FOCUS ::
  X Atom
atom_WM_TAKE_FOCUS =
  getAtom "WM_TAKE_FOCUS"

takeFocusX ::
  Window
  -> X ()
takeFocusX w =
  withWindowSet . const $ do
    dpy       <- asks display
    wmtakef   <- atom_WM_TAKE_FOCUS
    wmprot    <- atom_WM_PROTOCOLS
    protocols <- io $ getWMProtocols dpy w
    when (wmtakef `elem` protocols) $
      io . allocaXEvent $ \ev -> do
          setEventType ev clientMessage
          setClientMessageEvent ev w wmprot 32 wmtakef currentTime
          sendEvent dpy w False noEventMask ev

takeTopFocus ::
  X ()
takeTopFocus =
  withWindowSet $ maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek

My only hypothesis is that xmonad is not properly ignoring the panels.

I am using Ubuntu x64 12.10 upgraded from 12.04

EDIT: I tried adding className =? "mate-panel" --> doIgnore to manageHooks in xmonad.hs. No difference.

Était-ce utile?

La solution 2

Ah, I found it. I made a silly mistake in the manageHook part of the mateConfig section. The line manageHook = myManageHook <+> manageHook mateConfig doesn't really make sense because it is referring to mateConfig, which is still being defined by this line. It should actually be manageHook = myManageHook <+> manageHook desktopConfig. mateConfig should be desktopConfig.

Also, logHook, handleEventHook etc... are missing the <+> *Hook desktopConfig part, which breaks a whole bunch of stuff.

Autres conseils

I'm running MATE with XMonad. Check config. in this repo

Licencié sous: CC-BY-SA avec attribution
Non affilié à StackOverflow
scroll top