[xmonad] xmonad-x86_64-linux zero length ...

Jim Cheetham jim at gonzul.net
Tue Aug 31 16:36:34 EDT 2010


Recently (since I replaced two 19" monitors with 23" widescreen ones)
my XMonad window manager fails to startup (and gnome fails as well) in
an odd way that's almost indescribable (I sort-of get the desktop
background images badly positioned with one of them showing the red
border, and nothing else) -- and I noticed that the
xmonad-x86_64-linux file in ~./xmonad is zero length. Also a syslogged
message from gnome mentions problems :-

daemon.log:Sep  1 06:34:33 roro gnome-session[1492]: WARNING:
Application 'xmonad.desktop' failed to register before timeout

It looks like most of the files in ~/.xmonad are created around login
time, so I'm guessing something has gone wrong with compiling my
xmonad.hs -- but not every time, just sometimes. Possibly related to
when I've been using my laptop with the normal single screen, and then
later start up (cold boot) connected to dual external monitors on my
desk, but not all the time. The other possibility is that the DBus
hook I have in there (not understood, just cargo-coded from the web)
is causing issues ...

jim at roro:~/ISOs$ ls -l /home/jim/.xmonad/
total 7140
-rw-r--r-- 1 jim jim    2290 2010-08-30 09:52 revxmonad.png
-rw-r--r-- 1 jim jim       0 2010-09-01 06:37 xmonad.errors
-rw-r--r-- 1 jim jim    3715 2010-09-01 06:37 xmonad.hi
-rw-r--r-- 1 jim jim    6531 2010-08-30 09:51 xmonad.hs
-rw-r--r-- 1 jim jim  115440 2010-09-01 06:37 xmonad.o
-rwxr-xr-x 1 jim jim 7172303 2010-09-01 06:37 xmonad-x86_64-linux

Now, I could work around this by deleting these generated files, say
at system boot time ... but that seems a little wasteful. I'd rather
fix whatever is causing the problem in the first place ... This is the
Ubuntu 10.04 packaged version of Xmonad, and I'd rather stick with the
packaged version than have manually compiled code on the machine ...

jim at roro:~/.xmonad$ dpkg -l |grep xmonad
ii  libghc6-xmonad-contrib-dev                      0.9.1-1
                             Extensions to xmonad
ii  libghc6-xmonad-contrib-doc                      0.9.1-1
                             Extensions to xmonad; documentation
ii  libghc6-xmonad-dev                              0.9.1-2
                             A lightweight X11 window manager
ii  libghc6-xmonad-doc                              0.9.1-2
                             A lightweight X11 window manager;
documentation
ii  xmonad                                          0.9.1-2
                             A lightweight X11 window manager


Bits of xmonad.hs that might be relevant ...

{-# LANGUAGE ScopedTypeVariables #-} -- required in order to say
\(e::SomeException) in E.catch
import XMonad hiding ((|||)) -- get this from LayoutCombinators instead
-- For the DBus connectivity to xmonad-log-applet in the gnome-panel
import System.IO
import Control.Exception as E
import Control.Monad
import DBus
import DBus.Connection
import DBus.Message

main :: IO ()
-- main = do
main = withConnection Session $ \ dbus -> do
        spawn "notify-send -i /home/jim/.xmonad/revxmonad.png XMonad
'display manager reload'"
        getWellKnownName dbus

        xmonad $ gnomeConfig
                { modMask = mod4Mask -- Use the WindowsLogo key as the mod- key
--                , terminal = "gnome-terminal" -- set by Config.Gnome
                -- , terminal = "xterm"
                , manageHook = manageDocks <+> manageHook gnomeConfig
                , layoutHook = showWName myLayout
                , XMonad.workspaces = myWorkspaces
                , logHook = dynamicLogWithPP $ defaultPP
                        { ppOutput = myOutput dbus
                        , ppOrder = \(ws:l:t:_) -> [l,ws,t]
                        , ppTitle = pangoColor "#eeeeee" . shorten 54
. wrap "[<span font=\"Sans 10 Bold\">" "</span>]"-- Title of the
active window
                        , ppCurrent  = pangoColor "#eeeeee" . wrap
"<span font=\"Sans 10 Bold\">" "</span>" -- The currently active
workspace
                        , ppVisible  = pangoColor "#cccccc" . wrap
"<span font=\"Sans 10 Italic\">" "</span>" -- Workspaces on other
visible monitors
                        , ppHidden   = pangoColor "#aaaaaa" . wrap ""
"" -- Workspaces currently not visible
                        , ppUrgent = pangoColor "red" . wrap "!" "!"
-- +ppHidden
                        }
                }

-- Set up the connection to DBus
-- This retry is really awkward, but sometimes DBus won't let us get our
-- name unless we retry a couple times.
getWellKnownName :: Connection -> IO ()
getWellKnownName dbus = E.catch (tryGetName) (\(e::SomeException) ->
getWellKnownName dbus)
        where
                tryGetName = do
                namereq <- newMethodCall serviceDBus pathDBus
interfaceDBus "RequestName"
                addArgs namereq [String "org.xmonad.Log", Word32 5]
                sendWithReplyAndBlock dbus namereq 0
                return ()

-- Output logger stuff into dbus
myOutput dbus str = do
  let str'  = "<span font=\"Sans 10\"> " ++ str ++ "</span>"
      str'' = sanitize str'
  msg <- newSignal "/org/xmonad/Log" "org.xmonad.Log" "Update"
  addArgs msg [String str'']
  E.catch (send dbus msg 0) (\(e::SomeException) -> do return 0) --
ignore send errors, it wasn't that important
  return ()


More information about the xmonad mailing list