
Hello, On a fresh XMonad setup, I meet an issue and I'd like wise advices, wether I'm doing things correctly or not. I use two dzen, one for views, layout and title on the left and one for other things on right. The one on left is launched from within xmonad.hs via spawnpipe the one on right is lauched from my .xinitrc. If i make a change in xmonad.hs and want to recompile it, it compiles silently (no output with xmonad --recompile). All clients which were already here before the recompile won't cover the left dzen anymore after the recompile even with the mod-b shortcut (dzen stays on top) but they still cover the dzen on the right. All clients launched after the recompile behave the normal way, until I recompile ... My xmonad version : ~$ xmonad --version xmonad 0.9.1 (Source package xmonad and xmonad-contrib from Debian Sid) I attach my xmonad.hs I hope this message wasn't too confused. Julien

On Mon, Feb 22, 2010 at 03:34:54AM +0100, julien steinhauser wrote:
Hello,
On a fresh XMonad setup, I meet an issue and I'd like wise advices, wether I'm doing things correctly or not.
I use two dzen, one for views, layout and title on the left and one for other things on right.
The one on left is launched from within xmonad.hs via spawnpipe the one on right is lauched from my .xinitrc.
If i make a change in xmonad.hs and want to recompile it, it compiles silently (no output with xmonad --recompile).
All clients which were already here before the recompile won't cover the left dzen anymore after the recompile even with the mod-b shortcut (dzen stays on top) but they still cover the dzen on the right.
All clients launched after the recompile behave the normal way, until I recompile ...
My xmonad version : ~$ xmonad --version xmonad 0.9.1 (Source package xmonad and xmonad-contrib from Debian Sid)
I attach my xmonad.hs
I hope this message wasn't too confused.
Julien
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
Actually, my xmonad.hs is quite small, I reattached it not gunzipped for convenience. Sorry for double posting. Julien

On Mon, Feb 22, 2010 at 11:12:26AM +0100, julien steinhauser wrote:
On Mon, Feb 22, 2010 at 03:34:54AM +0100, julien steinhauser wrote:
Hello,
On a fresh XMonad setup, I meet an issue and I'd like wise advices, wether I'm doing things correctly or not.
I use two dzen, one for views, layout and title on the left and one for other things on right.
The one on left is launched from within xmonad.hs via spawnpipe the one on right is lauched from my .xinitrc.
If i make a change in xmonad.hs and want to recompile it, it compiles silently (no output with xmonad --recompile).
All clients which were already here before the recompile won't cover the left dzen anymore after the recompile even with the mod-b shortcut (dzen stays on top) but they still cover the dzen on the right.
All clients launched after the recompile behave the normal way, until I recompile ...
My xmonad version : ~$ xmonad --version xmonad 0.9.1 (Source package xmonad and xmonad-contrib from Debian Sid)
I attach my xmonad.hs
I hope this message wasn't too confused.
Julien
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
Actually, my xmonad.hs is quite small, I reattached it not gunzipped for convenience. Sorry for double posting.
Julien
import XMonad import Data.Monoid import System.Exit
import XMonad.Actions.DwmPromote import XMonad.Actions.CycleWS import XMonad.Actions.RotSlaves
import XMonad.Hooks.ManageDocks import XMonad.Hooks.DynamicLog
import XMonad.Layout.NoBorders import XMonad.Layout.TwoPane
import qualified XMonad.StackSet as W import qualified Data.Map as M
import XMonad.Util.Run
myTerminal = "urxvtc" myFocusFollowsMouse :: Bool myFocusFollowsMouse = True myBorderWidth = 1 myModMask = mod4Mask myWorkspaces = ["1","2","3","4"] myNormalBorderColor = "#000000" myFocusedBorderColor = "#00ff00"
myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $ [ ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) , ((modm, xK_p ), spawn "exe=`dmenu_path | xft_dmenu` && eval \"exec $exe\"") , ((modm, xK_s ), spawn "spawnsurf") , ((modm, xK_x ), spawn "actions") , ((modm, xK_r ), spawn "racine") , ((modm, xK_a ), spawn "setxkbmap fr") , ((modm, xK_q ), spawn "setxkbmap us") , ((modm, xK_l ), spawn "cd `cat /tmp/lastdir` && exec scd") , ((modm, xK_exclam), spawn "scd") , ((modm, xK_Insert), spawn "urxvtc -e vi ~/.xmonad/xmonad.hs") , ((modm, xK_m ), spawn "urxvtc -e mutt") , ((modm, xK_F1 ), spawn "dmenu_man") , ((modm .|. shiftMask, xK_p ), spawn "sdmenu_run") , ((modm, xK_w ), kill) , ((modm, xK_space ), sendMessage NextLayout) , ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf) , ((modm, xK_n ), refresh) , ((modm, xK_Tab ), windows W.focusDown) , ((modm .|. shiftMask, xK_Tab ), rotSlavesUp) , ((modm, 0x13bd ), windows W.focusUp ) , ((modm, xK_Return), dwmpromote ) , ((modm .|. shiftMask, xK_j ), windows W.swapDown ) , ((modm .|. shiftMask, xK_k ), windows W.swapUp ) , ((modm, xK_Left ), sendMessage Shrink) , ((modm, xK_Right ), sendMessage Expand) , ((modm .|. shiftMask, xK_t ), withFocused $ windows . W.sink) , ((modm , xK_comma ), sendMessage (IncMasterN 1)) , ((modm , xK_semicolon ), sendMessage (IncMasterN (-1))) , ((modm, xK_Down), nextWS) , ((modm, xK_Up), prevWS) , ((modm .|. shiftMask, xK_Down), shiftToNext) , ((modm .|. shiftMask, xK_Up), shiftToPrev) , ((modm .|. controlMask, xK_Down), shiftToNext >> nextWS) , ((modm .|. controlMask, xK_Up), shiftToPrev >> prevWS) , ((modm , xK_b ), sendMessage ToggleStruts) , ((modm .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) , ((modm .|. controlMask, xK_q ), spawn "xmonad --recompile; xmonad --restart") ] ++ [((m .|. modm, k), windows $ f i) | (i, k) <- zip (XMonad.workspaces conf) [0x26,0xe9,0x22,0x27] , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask) , (\i -> W.greedyView i . W.shift i, controlMask)]] ++ [((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f)) | (key, sc) <- zip [xK_z, xK_e] [0..] , (f, m) <- [(W.view, 0), (W.shift, shiftMask) , (\i -> W.view i . W.shift i, controlMask)]]
myLayout = smartBorders $ avoidStruts (tiled ||| Mirror tiled ||| TwoPane (3/100) (31/50) ||| Full) where tiled = Tall nmaster delta ratio nmaster = 1 ratio = 31/50 delta = 3/100
myManageHook = composeAll [ className =? "MPlayer" --> doFloat , className =? "Gimp" --> doFloat , resource =? "desktop_window" --> doIgnore ]
myEventHook = mempty myStartupHook = return ()
main = do h <- spawnPipe "dzen2 -w 1240 -ta l" xmonad $ defaultConfig { terminal = myTerminal, focusFollowsMouse = myFocusFollowsMouse, borderWidth = myBorderWidth, modMask = myModMask, workspaces = myWorkspaces, normalBorderColor = myNormalBorderColor, focusedBorderColor = myFocusedBorderColor, keys = myKeys, layoutHook = myLayout, manageHook = myManageHook <+> manageDocks, logHook = dynamicLogWithPP $ dzenPP { ppOutput = hPutStrLn h }, handleEventHook = myEventHook, startupHook = myStartupHook }
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
I solved it, I had to start the dzen which shows my workspaces, layout and title from my .xinitrc as well, like my other dzen.
participants (1)
-
julien steinhauser