You are not logged in.

#1 2009-08-22 23:18:28

soupcan
Member
From: ?
Registered: 2008-10-25
Posts: 268

[Solved] Help with workspaces in Xmonad

I'm using Xmonad for the first time, and I've stolen xmonad.hs and .xmobarrc from Taters. I changed the default modkey (alt) to the windows key. But changing workspaces is still eluding me. I've tried modkey + (number), but I don't see a blank workspace and Xmobar doesn't seem to indicate that I've changed workspaces- is it supposed to? If not, I'd like to make it do so.
Is there something blatantly obvious that I'm missing?

xmonad.hs:

-------------------- imports --------------------

--necessary
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) 

--utilities
import XMonad.Util.Run (spawnPipe)
import XMonad.Actions.NoBorders

--hooks
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.XPropManage

--MO' 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.Spacing
import Data.Ratio((%))


-------------------- main --------------------

main = do 
    h <- spawnPipe "xmobar ~/.xmobarrc"
    xmonad $ defaultConfig
        { workspaces = ["term", "web", "irc", "code", "else"]
        , modMask = mod4Mask
        , borderWidth = 1
        , normalBorderColor = "#3d352a"
        , focusedBorderColor = "#554444"
        , terminal = "urxvt"
        , logHook =  logHook' h
        , layoutHook = layoutHook'
        , keys = keys'
        }
-------------------- loghooks --------------------

logHook' :: Handle -> X ()
logHook' h = dynamicLogWithPP $ customPP { ppOutput = hPutStrLn h }

customPP :: PP
customPP = defaultPP { ppCurrent = xmobarColor "#cd5c5c" ""
             , ppTitle = shorten 75
             , ppSep = "<fc=#e8ae5b> | </fc>"
                     , ppHiddenNoWindows = xmobarColor "#a0a0a0" ""
                     }

-------------------- layouthooks --------------------

layoutHook' = customLayout
customLayout = avoidStrutsOn [u] (spaced ||| smartBorders tiled ||| smartBorders (Mirror tiled) ||| noBorders Full)
    where
     spaced = named "Spacing" $ spacing 6 $ Tall 1 (3/100) (1/2)
     tiled  = named "Tiled" $ ResizableTall 1 (2/100) (1/2) []

-------------------- menuhooks --------------------

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

-------------------- managehooks --------------------

myManageHook = composeAll . concat $
    [ [className =? c      --> doFloat | c <- myFloats]
    , [title =? t          --> doFloat | t <- myOtherFloats]
    , [className =? r      --> doIgnore | r <- myIgnores]

    , [className =? mp     --> doF (W.shift "mp") | mp <- mediaPlayers]
    , [className =? im     --> doF (W.shift "irc") | im <- imMessenger]
    , [className =? bw     --> doF (W.shift "www") | bw <- browsers]
    , [className =? e      --> doF (W.shift "else") | e <- elseApps]
    ]
    where
      myFloats = ["Gimp", "vlc", "Nitrogen", "Thunar", "Leafpad", "gmrun"]
      myOtherFloats = ["Downloads", "Firefox Preferences", "Save As...", "Send file", "Open", "File Transfers"]
      myIgnores = ["trayer", "stalonetray"]

      mediaPlayers = ["Quodlibet"]
      imMessenger = ["Pidgin"]
      browsers = ["Shiretoko", "Firefox"]
      elseApps = ["Mirage", "Gimp"]

-------------------- keybinds --------------------

keys' :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
keys' conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $

      --launching/killing
      [ ((modMask .|. shiftMask, xK_Return), spawn "gmrun")
      , ((modMask,         xK_Return), spawn $ XMonad.terminal conf)
      , ((modMask,               xK_f     ), spawn "firefox")
      , ((modMask .|. shiftMask, xK_m     ), spawn "urxvt -e ncmpcpp")
      , ((modMask .|. shiftMask, xK_c     ), kill)
      
      --layouts
      , ((modMask,               xK_space ), sendMessage NextLayout)
      , ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
      , ((modMask,               xK_b     ), sendMessage ToggleStruts)

      -- 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_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_F5]
          , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]

.xmobarrc:

Config { font = "-*-terminus-*-*-*-*-*-*-*-*-*-*-*-*"
       , bgColor = "#262729"
       , fgColor = "#a0a0a0"
       , position = Top
       , lowerOnStart = True
       , commands = [ Run Date "%A, %d %b %Y <fc=#cd5c5c>%H:%M:%S</fc>" "date" 10
                    , Run Com "skb" ["-1"] "kb" 10
                    , Run StdinReader
            , Run Com "mpc | grep -" [] "mpd" 10
                    ]
       , sepChar = "%"
       , alignSep = "}{"
       , template = "%StdinReader% }{<fc=#cd5c5c>%mpd%</fc> %date%  "
       }

Last edited by soupcan (2009-08-22 23:37:26)

Offline

#2 2009-08-22 23:25:44

&#32 Greg
Member
Registered: 2009-02-08
Posts: 80

Re: [Solved] Help with workspaces in Xmonad

Looking at the config, it seems like Taters made 5 named workspaces and assigned them to F1 through F5.

Offline

#3 2009-08-22 23:27:27

brisbin33
Member
From: boston, ma
Registered: 2008-07-24
Posts: 1,796
Website

Re: [Solved] Help with workspaces in Xmonad

that last part should be:

   [ ((m .|. modMask, k), windows $ f i)
   | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_5]                    -- %! Switch to workspace N
   , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]                      -- %! Move client to workspace N
   ]

you've got F's in yours, which i guess means M-F1 through F5 changes workspaces?

Offline

#4 2009-08-22 23:37:01

soupcan
Member
From: ?
Registered: 2008-10-25
Posts: 268

Re: [Solved] Help with workspaces in Xmonad

brisbin33 wrote:

that last part should be:

   [ ((m .|. modMask, k), windows $ f i)
   | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_5]                    -- %! Switch to workspace N
   , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]                      -- %! Move client to workspace N
   ]

you've got F's in yours, which i guess means M-F1 through F5 changes workspaces?

That's it! Like I said, I didn't actually write this, and I'm still unfamiliar with the syntax.
Thanks!

Offline

Board footer

Powered by FluxBB