You are not logged in.

#1 2007-12-04 19:12:01

thayer
Fellow
From: Vancouver, BC
Registered: 2007-05-20
Posts: 1,560
Website

xmonad Hacking Thread

What with such a small xmonad community, I thought it might be nice to have a central location here on the forums to discuss various tips & tricks. A place where you can post your xmonad.hs or snippets thereof and bounce around ideas for extensions and whatnot.

To get the ball rolling, I've included my config below, which is a heavily modified version of Robert Manea's (thanks gotmor!).  There are a couple of things not working for me at the moment (float hooks and persistent placed applications), but other than that it suits me fine.

For dzen and xmobar hacks, check out the dzen & xmobar Hacking Thread.

Update May 2011:

thumb-20110511-08.53.02-xmonad-dzen-conky.png

My current (Xmonad 0.9) configs can be found at github:  http://github.com/thayerwilliams

2007-12-12 screenshot and xmonad.hs:
thumb-20071212-2442186510.png

--
    -- ~/.xmonad/xmonad.hs
--

-- import the necessary libraries

import XMonad
import XMonad.ManageHook
import XMonad.Operations
import XMonad.Actions.CycleWS
import XMonad.Actions.DwmPromote
import XMonad.Actions.RotSlaves
import XMonad.Actions.RotView
import XMonad.Actions.SinkAll
import XMonad.Hooks.DynamicLog   ( PP(..), dynamicLogWithPP, dzenColor, wrap, defaultPP )
import XMonad.Layout 
import XMonad.Layout.Grid
import XMonad.Layout.NoBorders   ( noBorders, smartBorders )
import XMonad.Layout.Tabbed
import XMonad.Layout.ToggleLayouts
import XMonad.Util.Run

import qualified XMonad.StackSet as W
import qualified XMonad.Actions.FlexibleResize as Flex
import qualified Data.Map as M
import Data.Bits ((.|.))
import Data.Ratio
import Graphics.X11
import System.IO
 
statusBarCmd= "dzen2 -bg '#1a1a1a' -fg '#777777' -h 16 -w 550 -sa c -e '' -fn '-*-terminus-*-r-normal-*-*-120-*-*-*-*-iso8859-*' -ta l"
 
main = do din <- spawnPipe statusBarCmd
          xmonad $ defaultConfig
 
                     { borderWidth        = 2
                     , normalBorderColor  = "#333333"
                     , focusedBorderColor = "#ff0099" 
                     , workspaces         = ["1:main", "2:mail", "3:web"] ++ map show [4 .. 9 :: Int]
                     , terminal           = "urxvt"
                     , modMask            = mod1Mask
                     , defaultGaps        = [(16,0,0,0)]
                     , manageHook            = manageHook defaultConfig <+> myManageHook
                     , logHook            = dynamicLogWithPP $ myPP din
                               , layoutHook         = toggleLayouts (noBorders Full) $
                                            smartBorders $ tiled ||| Mirror tiled ||| Full ||| Grid ||| tabbed shrinkText defaultTConf
                     , keys               = \c -> myKeys c `M.union` keys defaultConfig c
                     , mouseBindings      = \c -> myMouse c `M.union` mouseBindings defaultConfig c
                     }
                     where
                     tiled   = Tall nmaster delta ratio

                     -- The default number of windows in the master pane
                     nmaster = 1

                     -- Default proportion of screen occupied by master pane
                     ratio   = 2/(1+(toRational(sqrt(5)::Double))) -- golden
                     
                     -- Percent of screen to increment by when resizing panes
                     delta   = 5%100


-- application control 
--
myManageHook :: ManageHook
myManageHook = composeAll . concat $
    [ [ className   =? c                 --> doFloat | c <- myFloats]
    , [ title       =? t                 --> doFloat | t <- myOtherFloats]
    , [ resource    =? r                 --> doIgnore | r <- myIgnores]
    , [ className   =? "Firefox-bin"     --> doF (W.shift "3:web") ]
    , [ className   =? "Opera"           --> doF (W.shift "3:web") ]
    , [ className   =? "Thunderbird-bin" --> doF (W.shift "2:mail") ]
    ]
    where
        myIgnores       = ["panel", "stalonetray", "trayer"]
        myFloats        = ["feh", "GIMP", "gimp", "gimp-2.4", "Galculator", "VirtualBox", "VBoxSDL"]
        myOtherFloats   = ["alsamixer", "Bon Echo Preferences", "Mail/News Preferences", "Bon Echo - Restore Previous Session"] 

-- modify/add default key binds
--
myKeys (XConfig {modMask = modm}) = M.fromList $
           [
           -- custom dmenu
           ((modm, xK_p), spawn "exe=`dmenu_path | dmenu -fn '-*-terminus-*-r-normal-*-*-120-*-*-*-*-iso8859-*' -nb '#000000' -nf '#FFFFFF' -sb '#0066ff'` && eval \"exec $exe\"") -- %! Launch dmenu
           -- sink all floating windows
           ,  ((modm .|. shiftMask, xK_t), sinkAll)
           -- swap focused with master, or master with next in line 
           , ((modm, xK_Return), dwmpromote)
           , ((modm, xK_KP_Enter), dwmpromote)
           -- rotate slave clients
           , ((modm .|. shiftMask, xK_Tab   ), rotSlavesUp)
           -- cycle through non-empty workspaces
           , ((modm .|. shiftMask, xK_Right), rotView True)
           , ((modm .|. shiftMask, xK_Left), rotView False)
           -- switch to previous workspace
           , ((modm, xK_z), toggleWS)
           -- toggle to fullscreen.
           , ((modm, xK_x), sendMessage ToggleLayout)
           -- session management
           , ((modm .|. shiftMask .|. controlMask, xK_k), spawn "xkill")
           , ((modm .|. shiftMask .|. controlMask, xK_End), spawn "sudo shutdown -h now")
           , ((modm .|. shiftMask .|. controlMask, xK_Delete), spawn "sudo shutdown -r now")
           , ((mod4Mask, xK_l), spawn "xscreensaver-command --lock")
           -- application hotkeys
           , ((mod4Mask, xK_w), spawn "firefox")
           , ((mod4Mask, xK_t), spawn "thunderbird")
           , ((mod4Mask, xK_e), spawn "thunar")
           , ((mod4Mask, xK_v), spawn "urxvt -e alsamixer")
           , ((0, xK_Print), spawn "scrot %Y%m%d-dublin.png -t 280x175")
           , ((shiftMask, xK_Print), spawn "scrot %Y%m%d-dublin.png -d 3 -t 280x175")
           ]
 
-- modify/add default mouse binds
-- 
myMouse (XConfig {modMask = modm}) = M.fromList $
           [ ((modm, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
           , ((modm, button4), (\_ -> rotView True)) 
           , ((modm, button5), (\_ -> rotView False))
           ]

-- dynamiclog pretty printer for dzen
--
myPP h = defaultPP 
                 { ppCurrent = wrap "^fg(#ffffff)^bg(#0066ff)^p(2)^i(/home/thayer/.xmonad/dzen/marker.xbm)" "^p(2)^fg()^bg()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId    -- Trim the '[Int]:' from workspace tags
                  , ppVisible = wrap "^bg(grey30)^fg(grey75)^p(2)" "^p(2)^fg()^bg()"
                  , ppHidden = wrap "^fg(#ffffff)^bg()^p(2)^i(/home/thayer/.xmonad/dzen/marker.xbm)" "^p(2)^fg()^bg()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
                  , ppHiddenNoWindows = id . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
                  , ppSep     = "  ^fg(#ffffff)^r(2x2)^fg()  "
                  , ppWsSep           = " "
                  , ppLayout  = dzenColor "#cccccc" "" .
                                (\x -> case x of
                                         "Tall" -> "tall ^i(/home/thayer/.xmonad/dzen/layout-tall.xbm)"
                                         "Mirror Tall" -> "mirror ^i(/home/thayer/.xmonad/dzen/layout-mtall.xbm)"
                                         "Full" -> "full ^i(/home/thayer/.xmonad/dzen/layout-full.xbm)"
                                         "Grid" -> "grid"
                                         "Tabbed" -> "tabbed"
                                )
--                  , ppTitle   = dzenColor "white" "" . wrap "< " " >" 
                  , ppTitle   = dzenColor "white" ""
                  , ppOutput   = hPutStrLn h
                  }

Last edited by thayer (2013-05-10 21:56:36)


thayer williams ~ cinderwick.ca

Offline

#2 2007-12-04 20:41:30

buttons
Member
From: NJ, USA
Registered: 2007-08-04
Posts: 620

Re: xmonad Hacking Thread

I kinda wonder if anyone didn't base theirs off Rob's, if simply for the excellent dynamicLog printer.

-- xmonad.hs
import XMonad
import XMonad.Layouts
import XMonad.Config                (defaultConfig)
import XMonad.Actions.RotView        ( rotView )
import XMonad.Hooks.DynamicLog        ( PP(..), dynamicLogWithPP, dzenColor, wrap, defaultPP )
import XMonad.Layout.NoBorders
import XMonad.Util.Run                (spawnPipe)
import Data.Bits

import XMonad.Operations
import qualified XMonad.StackSet as W 
import qualified Data.Map as Map
import Data.Ratio
import Graphics.X11.Xlib
import System.IO
 
statusBarCmd= "dzen2 -y 1010 -bg '#000000' -fg 'grey70' -sa c -fn '-*-terminus-*-*-*-*-12-*-*-*-*-*-iso8859' -e '' -ta l -w 600"
 
main = do din <- spawnPipe statusBarCmd
          xmonad $ defaultConfig
                     { borderWidth        = 1
                     , normalBorderColor  = "black"
                     , focusedBorderColor = "green"
                     , terminal           = "urxvt"
                     , workspaces         = ["main","net","dev"]
                                            ++ map show [4..9]
                     , defaultGaps        = [(30,14,0,0)]
                     , logHook            = dynamicLogWithPP $ myPP din
                     , manageHook          = myManageHook
                     , modMask            = mod4Mask
                     , keys               = \c -> myKeys `Map.union`
                                                  keys defaultConfig c
                     , layoutHook         = smartBorders $ Mirror tiled ||| Full ||| tiled
                     }
                     where
                        tiled = Tall 1 (3%100) (680%1000)
 
myKeys = Map.fromList $
    [ ((mod4Mask                    , xK_F2    ), spawn "gmrun")
    --, ((mod4Mask .|. shiftMask        , xK_t       ), spawn "thunar")
    , ((mod4Mask                    , xK_e       ), spawn "thunar")
    , ((mod4Mask                    , xK_o       ), spawn "urxvt -e screen")
    , ((mod4Mask                    , xK_F12   ), spawn "sudo shutdown -h now")
    , ((mod4Mask                    , xK_p     ), spawn "exe=`dmenu_path | dmenu -b -fn '-*-terminus-*-r-*-*-*-*-*-*-*-*-*-*' -nb '#000000' -nf '#FFFFFF'` && eval \"exec $exe\"") -- %! Launch dmenu
    , ((mod4Mask                    , xK_c       ), kill)
    ]

myManageHook = composeAll . concat $
                [ [ className =? c --> doFloat | c <- floats]
                , [ resource =? r --> doIgnore | r <- ignore]
                , [ resource =? "gecko" --> doF (W.shift "net") ]]
 where floats = ["MPlayer", "Gimp"]
       ignore = ["panel", "trayer"]

myPP h = defaultPP 
            { ppCurrent = wrap "^fg(#000000)^bg(#a6c292)^p(2)^i(/home/buttons/.bitmaps/has_win.xbm)" "^p(2)^fg()^bg()"
             , ppVisible = wrap "^bg(grey30)^fg(grey75)^p(2)" "^p(2)^fg()^bg()"
             , ppSep     = " ^fg(grey60)^r(3x3)^fg() "
             , ppLayout  = dzenColor "#80AA83" "" .
                           (\x -> case x of
                                    "Tall" -> "^i(/home/buttons/.bitmaps/tall.xbm)"
                                    "Mirror Tall" -> "^i(/home/buttons/.bitmaps/mtall.xbm)"
                                    "Full" -> "^i(/home/buttons/.bitmaps/full.xbm)"
                           )
             , ppTitle   = dzenColor "white" "" . wrap "< " " >" 
             , ppOutput   = hPutStrLn h
             }

I've gotta say, the darcs version makes configuration SO much more readable, not to mention less time-consuming.


Cthulhu For President!

Offline

#3 2007-12-04 23:13:52

dimaka
Member
From: Ukraine, Bila Tserkva
Registered: 2006-11-23
Posts: 35
Website

Re: xmonad Hacking Thread

When I watch the movie with Mplayer in fullscreen, it has visible border sad How can I remove or hide it?

Offline

#4 2007-12-04 23:16:58

thayer
Fellow
From: Vancouver, BC
Registered: 2007-05-20
Posts: 1,560
Website

Re: xmonad Hacking Thread

Have a look at the XMonad.Layout.NoBorders extension... That's exactly what it does.  Both our configs (mine and buttons) make use of it's smartBorders functions, which basically strips the border from a client when it's fullscreen or when it's the only client on a particular workspace.


thayer williams ~ cinderwick.ca

Offline

#5 2007-12-05 02:19:36

thayer
Fellow
From: Vancouver, BC
Registered: 2007-05-20
Posts: 1,560
Website

Re: xmonad Hacking Thread

Does anyone know if it's possible to differentiate between Thunderbird and Firefox with respect to determining which workspace they load in?

I would like to start each on their respective workspace, but they both use "gecko" as the primary WM_CLASS.  I tried using Thunderbird-bin and Firefox-bin, the secondary WM_CLASS names, but that doesn't work.


thayer williams ~ cinderwick.ca

Offline

#6 2007-12-05 06:07:47

semdornus
Member
From: Tokyo
Registered: 2007-08-07
Posts: 47

Re: xmonad Hacking Thread

thayer wrote:

Does anyone know if it's possible to differentiate between Thunderbird and Firefox with respect to determining which workspace they load in?

, workspaces         = ["1:web", "2:mail", "3:dev", "4:float"] ++ map show [5 .. 9 :: Int]

myManageHook = composeAll . concat $
                [ [ className =? c --> doFloat | c <- floats]
                , [ className =? "Firefox-bin" --> doF (W.shift "web") ]
                , [ className =? "Thunderbird-bin" --> doF (W.shift "1:mail") ]]
    where floats = ["VLC media player", "MPlayer", "Gimp","xli","Xmessage"]

If that's the exact config you're using then it's not working because the workspace names don't match. The hook for firefox doesn't include the number of the workspace and the thunderbird one has the wrong number. You've probably been experimenting and re-ordering workspaces, right? wink If you match them it should work.

If there's interest I'll post my config later when I get home from work. I took some ideas from most of the configs on the wiki and added some stuff.

Edit: typo

Last edited by semdornus (2007-12-05 06:09:43)

Offline

#7 2007-12-05 08:27:36

dimaka
Member
From: Ukraine, Bila Tserkva
Registered: 2006-11-23
Posts: 35
Website

Re: xmonad Hacking Thread

thayer wrote:

Have a look at the XMonad.Layout.NoBorders extension... That's exactly what it does.  Both our configs (mine and buttons) make use of it's smartBorders functions, which basically strips the border from a client when it's fullscreen or when it's the only client on a particular workspace.

Thanks. But the problem is still present. I am a newbie to xmonad, so I've used yours and button's configs, but mplayer in fullscreen still has borders, except urxvt for example, it doesn't have borders when in fullscreen, same as inactive windows.

Offline

#8 2007-12-05 08:49:08

Gilneas
Member
From: Netherlands
Registered: 2006-10-22
Posts: 320

Re: xmonad Hacking Thread

Try using mplayer -fstype none, or something like that. I think 'none' makes it behave like normal windows.

Offline

#9 2007-12-05 10:13:18

dimaka
Member
From: Ukraine, Bila Tserkva
Registered: 2006-11-23
Posts: 35
Website

Re: xmonad Hacking Thread

It didn't help neutral I also try to use -fstype below (I thought it will make fullscreen mplayer like inactive window) but it didn't help either...
btw - other soft like swiftfox, amule works in fullscreen without borders too. So the problem for the moment is only with mplayer.

Last edited by dimaka (2007-12-05 10:15:09)

Offline

#10 2007-12-05 10:34:14

dimaka
Member
From: Ukraine, Bila Tserkva
Registered: 2006-11-23
Posts: 35
Website

Re: xmonad Hacking Thread

The simple solution is to press mod+tab, to make mplayer window inactive. I am using button's config now (where borders of inactive windows are black or disabled...) /me gonna to smoke out that config :-D

Last edited by dimaka (2007-12-05 10:34:35)

Offline

#11 2007-12-05 14:42:52

semdornus
Member
From: Tokyo
Registered: 2007-08-07
Posts: 47

Re: xmonad Hacking Thread

OK, my config. Still really not happy with the colors so I'm going to play with that some more. I also haven't decided yet if I want to use more XPMs for layouts and more graphical info in the statusbar...

-- Last modified: 2007-12-05 23:26:33

{-# OPTIONS_GHC -Wall -Werror #-}
-- Imports {{{
-- System {{{
-- GHC
import Data.Bits                                                (Bits((.|.)))
import Data.Map as M                                            (M.fromList, M.union, M.Map)
import Graphics.X11
import System.IO.UTF8                                           (hPutStrLn)

-- XMonad core
import XMonad                                                   (XConfig(..), Layout(..), ManageHook, X, xmonad)
import XMonad.Config                                            (defaultConfig)
import XMonad.Layouts                                           (Full(..), Mirror(..), Tall(..))
-- import XMonad.ManageHook
import XMonad.ManageHook                                        (composeAll, doFloat, doF, className, title, (<+>), (=?), (-->))
import XMonad.Operations                                        (sendMessage, focus, windows)
import XMonad.StackSet as W                                     (W.shift, W.greedyView)
-- }}}

-- Contributions {{{
import XMonad.Actions.CopyWindow                                (copy, kill1)
import XMonad.Actions.CycleWS                                   (prevWS, nextWS, toggleWS, shiftToNext, shiftToPrev)
import XMonad.Actions.DwmPromote                                (dwmpromote)
import XMonad.Actions.DynamicWorkspaces                         (removeWorkspace, renameWorkspace, withWorkspace, withNthWorkspace, selectWorkspace)
import qualified XMonad.Actions.FlexibleManipulate as Flex      (Flex.mouseWindow, Flex.linear)
import XMonad.Actions.RotView                                   (rotView)

import XMonad.Hooks.DynamicLog                                  (PP(..), dynamicLogWithPP, dzenColor, defaultPP, shorten, dzenEscape)
import XMonad.Hooks.SetWMName                                   (setWMName)
import XMonad.Hooks.UrgencyHook                                 (withUrgencyHook, dzenUrgencyHook, focusUrgent, args)

import XMonad.Layout.LayoutCombinators
import XMonad.Layout.Named
import XMonad.Layout.NoBorders                                  (noBorders)
import XMonad.Layout.Tabbed                                     (tabbed, defaultTConf, TConf(..), shrinkText)
import XMonad.Layout.ToggleLayouts
import XMonad.Layout.WindowNavigation                           (Navigate(..), Direction(..), windowNavigation)

import XMonad.Prompt                                            (XPPosition(Bottom), XPConfig(..), defaultXPConfig)
import XMonad.Prompt.Man                                        (manPrompt)
import XMonad.Prompt.Shell                                      (shellPrompt)
import XMonad.Prompt.Window                                     (windowPromptGoto, windowPromptBring)
import XMonad.Prompt.XMonad                                     (xmonadPrompt)

import XMonad.Util.Run                                          (spawnPipe, safeSpawn, unsafeSpawn, runInTerm)
-- }}}
-- }}}

-- Main execution and configuration {{{
-- Set statusbar program and parameters
statusBarCmd :: String
statusBarCmd = "dzen2 -e '' -w 900 -ta l -fg \"#ccc\" -bg \"#2A2733\" -fn \"-*-terminus-*-*-*-*-12-*-*-*-*-*-iso10646-1\""

main :: IO()
main = do
    din <- spawnPipe statusBarCmd
    xmonad
        $ withUrgencyHook dzenUrgencyHook {args = ["-bg", "yellow", "-fg", "black"]}
        $ defaultConfig
        { normalBorderColor     = "#ccc"
        , focusedBorderColor    = "#CAFF42"
        , terminal              = "urxvt"
        , workspaces            = ["1:main", "2:fs", "3:web", "4:irc", "5:tmp"]   -- Start with numbers because of DynamicWorkspaces
        -- ++ map show [7 .. 9 :: Int]
        , defaultGaps           = [(14,0,0,0)]
        , modMask               = mod4Mask
        , logHook               = dynamicLogWithPP $ myPP {ppOutput = hPutStrLn din}
        , keys                  = \c -> myKeys c `M.union` keys defaultConfig c
        , mouseBindings         = \c -> myMouse c `M.union` mouseBindings defaultConfig c
        , manageHook            = manageHook defaultConfig <+> myManageHook
        , layoutHook            = windowNavigation $
                                    toggleLayouts (Named "Full" (noBorders Full)) $
                                        Named "Vert" tiled
                                    ||| Named "Wide" (tiled ****//* tiled)
                                    ||| Named "Tab" (noBorders myTab)
                                    ||| Named "Horiz" (Mirror tiled)
                                    -- ||| Named "Test1" (combineTwo (TwoPane 0.03 0.5) (myTab) (myTab))
                                    -- ||| Named "Test2" (myTab ***/**** Full)
                                    -- ||| Named "Wide" ((myTab *||* myTab) **//* combineTwo Square myTab myTab)
        }
        where
            tiled = Tall 1 0.03 0.68                -- Tall <nmaster> <delta> <ratio>
            myTab = tabbed shrinkText myTabConfig
-- }}}

-- Move programs to specific workspace and float some {{{
myManageHook :: ManageHook
myManageHook = composeAll . concat $
    [ [ className   =? c                --> doFloat | c <- myFloats]
    , [ title       =? t                --> doFloat | t <- myOtherFloats]
    , [ className   =? "Firefox"        --> doF (W.shift "3:web") ]
    , [ className   =? "Opera"          --> doF (W.shift "3:web") ]
    , [ className   =? "Thunar"         --> doF (W.shift "2:fs") ]
    , [ className   =? "Grisbi"         --> doF (W.shift "5:tmp") ]
    , [ className   =? "GQview"         --> doF (W.shift "5:tmp") ]
    , [ className   =? "Gimp"           --> doF (W.shift "5:tmp") ]
    ]
    where
        myFloats        = ["feh", "gimp"]
        myOtherFloats   = ["Firefox Preferences", "Element Properties"]
-- }}}

-- Custom key bindings {{{
myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
myKeys (XConfig {modMask = modm}) = M.fromList$
    -- Overrides and general {{{
    -- mod-[1..9] %! Switch to workspace N
    zip (zip (repeat modm) [xK_1..xK_9]) (map (withNthWorkspace W.greedyView) [0..])
    ++
    -- mod-shift-[1..9] %! Move client to workspace N
    zip (zip (repeat (modm .|. shiftMask)) [xK_1..xK_9]) (map (withNthWorkspace W.shift) [0..])
    ++
    -- mod-control-shift-[1..9] Copy client to workspace N
    zip (zip (repeat (modm .|. controlMask)) [xK_1..xK_9]) (map (withNthWorkspace copy) [0..]) 
    ++
    [ ((modm                                , xK_BackSpace  ), focusUrgent                                              )   -- Focuses the most recently urgent client
    , ((modm                                , xK_Return     ), dwmpromote                                               )   -- Dwm-like master swap function
    , ((modm .|. controlMask                , xK_space      ), sendMessage ToggleLayout                                 )   -- Toggle layout (to Full) and back
    , ((modm .|. shiftMask                  , xK_c          ), kill1                                                    )   -- Close the current client

    -- Java hack
    , ((modm                                , xK_z          ), setWMName "LG3D"                                         )   -- Set WM name before java execution to avoid grey blobs
    -- }}}

    -- Workspace management {{{
    , ((0                                   , 0x1008ff26    ), prevWS                                                   )   -- XF86Back: Switch to next workspace
    , ((0                                   , 0x1008ff27    ), nextWS                                                   )   -- XF86Forward: Switch to previous workspace
    , ((0 .|. shiftMask                     , 0x1008ff26    ), shiftToPrev                                              )   -- XF86Back: Move the current client to the previous workspace
    , ((0 .|. shiftMask                     , 0x1008ff27    ), shiftToNext                                              )   -- XF86Forward: Move the current client to the next workspace
    , ((0 .|. controlMask                   , 0x1008ff26    ), shiftToPrev >> prevWS                                    )   -- XF86Back: Move the current client to the previous workspace and go there
    , ((0 .|. controlMask                   , 0x1008ff27    ), shiftToNext >> nextWS                                    )   -- XF86Forward: Move the current client to the next workspace and go there
    , ((modm                                , xK_v          ), selectWorkspace myPromptConfig                           )   -- Prompt for a workspace to switch to
    , ((modm                                , xK_w          ), toggleWS                                                 )   -- Toggle to the workspace previously displayed
    , ((modm .|. controlMask                , xK_m          ), withWorkspace myPromptConfig (windows . copy)            )   -- Prompt for a new workspace and copy all client from the current one there
    , ((modm .|. shiftMask                  , xK_BackSpace  ), removeWorkspace                                          )   -- Remove current workspace (must be empty)
    , ((modm .|. shiftMask                  , xK_b          ), windowPromptBring myPromptConfig                         )   -- Prompt for client title and bring it to the current workspace
    , ((modm .|. shiftMask                  , xK_g          ), windowPromptGoto  myPromptConfig                         )   -- Prompt for client title and go to the workspace containing it
    , ((modm .|. shiftMask                  , xK_m          ), withWorkspace myPromptConfig (windows . W.shift)         )   -- Prompt for a new workspace and move all client from the current one there
    , ((modm .|. shiftMask                  , xK_r          ), renameWorkspace myPromptConfig                           )   -- Prompt for a new name for the current workspace
    , ((modm .|. shiftMask .|. controlMask  , xK_Left       ), rotView False                                            )   -- Cycle through non-empty workspaces after the current
    , ((modm .|. shiftMask .|. controlMask  , xK_Right      ), rotView True                                             )   -- Cycle through non-empty workspaces before the current
    -- }}}

    -- Window management {{{
    , ((modm                                , xK_Right      ), sendMessage $ Go R                                       )   -- Go to client on the right
    , ((modm                                , xK_Left       ), sendMessage $ Go L                                       )   -- Go to client on the left
    , ((modm                                , xK_Up         ), sendMessage $ Go U                                       )   -- Go to client above
    , ((modm                                , xK_Down       ), sendMessage $ Go D                                       )   -- Go to client below
    , ((modm .|. shiftMask                  , xK_Right      ), sendMessage $ Swap R                                     )   -- Swap current client with the one on the right
    , ((modm .|. shiftMask                  , xK_Left       ), sendMessage $ Swap L                                     )   -- Swap current client with the one on the left
    , ((modm .|. shiftMask                  , xK_Up         ), sendMessage $ Swap U                                     )   -- Swap current client with the one above
    , ((modm .|. shiftMask                  , xK_Down       ), sendMessage $ Swap D                                     )   -- Swap current client with the one below
    , ((modm .|. controlMask                , xK_Right      ), sendMessage $ Move R                                     )   -- Move client to the sub layout on the right
    , ((modm .|. controlMask                , xK_Left       ), sendMessage $ Move L                                     )   -- Move client to the sub layout on the left
    , ((modm .|. controlMask                , xK_Up         ), sendMessage $ Move U                                     )   -- Move client to the sub layout above
    , ((modm .|. controlMask                , xK_Down       ), sendMessage $ Move D                                     )   -- Move client to the sub layout below
    -- }}}

    -- Programs {{{
    , ((0                                   , 0x1008ff11    ), unsafeSpawn "amixer -q set PCM 2dB-"                     )   -- XF86AudioLowerVolume: Lower audio volume
    , ((0                                   , 0x1008ff12    ), unsafeSpawn "amixer -q set PCM toggle"                   )   -- XF86AudioMute: Mute audio
    , ((0                                   , 0x1008ff13    ), unsafeSpawn "amixer -q set PCM 2dB+"                     )   -- XF86AudioRaiseVolume: Raise audio volume
    , ((0                                   , 0x1008ff14    ), safeSpawn "mpc" "toggle"                                 )   -- XF86AudioPlay: MPD: Toggle pause/play
    , ((0                                   , 0x1008ff15    ), safeSpawn "mpc" "stop"                                   )   -- XF86AudioStop: MPD: Stop
    , ((0                                   , 0x1008ff16    ), safeSpawn "mpc" "prev"                                   )   -- XF86AudioPrev: MPD: Go to previous song
    , ((0                                   , 0x1008ff17    ), safeSpawn "mpc" "next"                                   )   -- XF86AudioNext: MPD: Go to next song
    , ((0                                   , 0x1008ff18    ), safeSpawn "firefox" ""                                   )   -- XF86HomePage: Launch Firefox
    , ((0                                   , 0x1008ff19    ), runInTerm "screen -D -R mail mutt"                       )   -- XF86Mail: Launch mutt in a named screen session
    , ((0                                   , 0x1008ff1b    ), shellPrompt myPromptConfig                               )   -- XF86Search: Prompt for commandline to execute
    , ((0                                   , 0x1008ff1d    ), unsafeSpawn "xcalc"                                      )   -- XF86Calculator: Launch xcalc
    , ((0 .|. shiftMask                     , 0x1008ff19    ), safeSpawn "thunderbird" ""                               )   -- XF86Mail: Launch Thunderbird
    , ((0 .|. shiftMask                     , 0x1008ff1b    ), manPrompt myPromptConfig                                 )   -- XF86Search: Prompt for manual page to be displayed
    , ((0 .|. controlMask                   , 0x1008ff1b    ), xmonadPrompt myPromptConfig                              )   -- XF86Search: Prompt for xmonad comand
    , ((modm                                , xK_Print      ), unsafeSpawn "import -quality 90 -window root png:$HOME/desktop-$(date +%F).png") -- Make a screenshot of the desktop
    , ((modm                                , xK_e          ), runInTerm "elinks"                                       )   -- Launch elinks in a terminal
    , ((modm                                , xK_i          ), runInTerm "screen -D -R irc irssi"                       )   -- Launch irssi in a named screen session
    , ((modm                                , xK_r          ), runInTerm "screen -D -R leech rtorrent"                  )   -- Launch rtorrent in a named screen session
    , ((modm .|.shiftMask .|. controlMask   , xK_Return     ), runInTerm "screen -D -R main"                            )   -- Launch terminal in a named screen session
    ]
    --- }}}
-- }}}

-- Custom mouse actions {{{
myMouse :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
myMouse (XConfig {modMask = modm}) = M.fromList$
    [ ((modm                                , button3       ), (\w -> focus w >> Flex.mouseWindow Flex.linear w)        )   -- Resize client perserving its aspect
    , ((modm                                , button4       ), (\_ -> nextWS)                                           )   -- Mouse scrollwheel up: Switch to next workspace
    , ((modm                                , button5       ), (\_ -> prevWS)                                           )   -- Mouse scrollwheel down: Switch to previous workspace
    ]
-- }}}

-- The prompt config {{{
myPromptConfig :: XPConfig
myPromptConfig = defaultXPConfig
    { position          = Bottom
    , promptBorderWidth = 0
    , font              = "-*-terminus-*-*-*-*-12-*-*-*-*-*-iso10646-1"
    , height            = 14
    , bgColor           = "#2A2733"
    , fgColor           = "#AA9DCF"
    , bgHLight          = "#6B6382"
    , fgHLight          = "#4A4459"
    }
-- }}}

-- The tab layout config {{{
myTabConfig :: TConf
myTabConfig = defaultTConf
    { activeColor         = "#8a999e"
    , inactiveColor       = "#545d75"
    , activeBorderColor   = "white"
    , inactiveBorderColor = "grey"
    , activeTextColor     = "white"
    , inactiveTextColor   = "grey"
    , tabSize             = 14
    , fontName            = "-*-terminus-*-*-*-*-12-*-*-*-*-*-iso10646-1"
    }
-- }}}

-- The logHook pretty-printer {{{
myPP :: PP
myPP = defaultPP
    { ppCurrent         = dzenColor "#4A4459" "#CAFF42" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId    -- If the workspace name contains a ':' then drop the first 2 characters of the workspace name to remove the numbers
    , ppVisible         = dzenColor "#8B80A8" ""
    , ppHidden          = dzenColor "#6B6382" "" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppHiddenNoWindows = dzenColor "#4A4459" "" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppLayout          = dzenColor "#6B6382" ""
    , ppSep             = "  "
    , ppWsSep           = " "
    , ppTitle           = dzenColor "#AA9DCF" "". shorten 700 . dzenEscape
    }
{-
    , ppLayout   = dzenColor "black" "#cccccc" .
        (\ x -> case x of
            "TilePrime Horizontal" -> "^i(/home/../images/tile_horz.xpm)"
            "TilePrime Vertical"   -> "^i(/home/../images/tile_vert.xpm)"
            "Hinted Full"          -> "^i(/home/../images/fullscreen.xpm)"
            _                      -> pad x
        )
-}
-- }}}
-- vim: fdm=marker ts=4 sw=4 sts=4 et:

Looks like http://omploader.org/vODkw

Edit: typo again

Last edited by semdornus (2007-12-05 14:45:07)

Offline

#12 2007-12-05 15:37:43

thayer
Fellow
From: Vancouver, BC
Registered: 2007-05-20
Posts: 1,560
Website

Re: xmonad Hacking Thread

semdornus wrote:
thayer wrote:

, [ className =? "Firefox-bin" --> doF (W.shift "web") ]
                , [ className =? "Thunderbird-bin" --> doF (W.shift "1:mail") ]]

If that's the exact config you're using then it's not working because the workspace names don't match. The hook for firefox doesn't include the number of the workspace and the thunderbird one has the wrong number. You've probably been experimenting and re-ordering workspaces, right? wink If you match them it should work.

I was just too lazy to revert it back to my original non-working syntax.  It still does not work if I properly declare the workspaces.

I just tried your config settings and they don't work for me either.  Are you using the default Firefox and Thunderbird in the repos?  If so, I don't know where you are getting the className from because according to xprop my Thunderbird is titled "Inbox - Mail/News" and my Firefox is titled "Google - Bon Echo" depending on the homepage.

SOLVED:

Thanks, semdornus.  For some reason the syntax I was using to call the manageHook extension wasn't working with the Thunderbird-bin and Firefox-bin class names.  I changed my config to match your entire manageHook arrays, replacing Firefox with Firefox-bin and now everything works.  For the record, I'm guessing you are running the non-Arch Firefox/Thunderbird builds since Arch uses Bon Echo.

Thanks again

Last edited by thayer (2007-12-05 15:58:25)


thayer williams ~ cinderwick.ca

Offline

#13 2007-12-06 00:22:58

semdornus
Member
From: Tokyo
Registered: 2007-08-07
Posts: 47

Re: xmonad Hacking Thread

thayer wrote:

For the record, I'm guessing you are running the non-Arch Firefox/Thunderbird builds since Arch uses Bon Echo.

Sorry for the confusion. That's correct; at the moment I'm not running Arch, so the classnames and/or titles in the hooks could differ.

Offline

#14 2007-12-06 00:28:13

thayer
Fellow
From: Vancouver, BC
Registered: 2007-05-20
Posts: 1,560
Website

Re: xmonad Hacking Thread

semdornus wrote:

Sorry for the confusion. That's correct; at the moment I'm not running Arch, so the classnames and/or titles in the hooks could differ.

No worries... thanks very much for the help.


thayer williams ~ cinderwick.ca

Offline

#15 2007-12-07 05:06:41

buttons
Member
From: NJ, USA
Registered: 2007-08-04
Posts: 620

Re: xmonad Hacking Thread

semdornus wrote:

OK, my config. Still really not happy with the colors so I'm going to play with that some more. I also haven't decided yet if I want to use more XPMs for layouts and more graphical info in the statusbar...

-- Last modified: 2007-12-05 23:26:33
Some code...

Oh man, thank you!  I desperately needed some way of setting up multimedia keys on my laptop (lineakd just crashes every time I hit a key twice), and your config had it all in there.  Excellent.


Cthulhu For President!

Offline

#16 2007-12-07 05:58:06

semdornus
Member
From: Tokyo
Registered: 2007-08-07
Posts: 47

Re: xmonad Hacking Thread

buttons wrote:

Oh man, thank you!  I desperately needed some way of setting up multimedia keys on my laptop (lineakd just crashes every time I hit a key twice), and your config had it all in there.  Excellent.

NP. Glad somebody had some use out of it. I don't know if you have more/other keys then I have on your keyboard, but you can find your codes by using the xev utility to look up the code.

Offline

#17 2007-12-10 21:18:08

JoyFM
Member
From: potsdam
Registered: 2007-01-03
Posts: 27
Website

Re: xmonad Hacking Thread

buttons wrote:

I kinda wonder if anyone didn't base theirs off Rob's, if simply for the excellent dynamicLog printer.

-- xmonad.hs
import XMonad
import XMonad.Layouts
import XMonad.Config                (defaultConfig)
import XMonad.Actions.RotView        ( rotView )
import XMonad.Hooks.DynamicLog        ( PP(..), dynamicLogWithPP, dzenColor, wrap, defaultPP )
import XMonad.Layout.NoBorders
import XMonad.Util.Run                (spawnPipe)
import Data.Bits

import XMonad.Operations
import qualified XMonad.StackSet as W 
import qualified Data.Map as Map
import Data.Ratio
import Graphics.X11.Xlib
import System.IO
 
statusBarCmd= "dzen2 -y 1010 -bg '#000000' -fg 'grey70' -sa c -fn '-*-terminus-*-*-*-*-12-*-*-*-*-*-iso8859' -e '' -ta l -w 600"
 
main = do din <- spawnPipe statusBarCmd
          xmonad $ defaultConfig
                     { borderWidth        = 1
                     , normalBorderColor  = "black"
                     , focusedBorderColor = "green"
                     , terminal           = "urxvt"
                     , workspaces         = ["main","net","dev"]
                                            ++ map show [4..9]
                     , defaultGaps        = [(30,14,0,0)]
                     , logHook            = dynamicLogWithPP $ myPP din
                     , manageHook          = myManageHook
                     , modMask            = mod4Mask
                     , keys               = \c -> myKeys `Map.union`
                                                  keys defaultConfig c
                     , layoutHook         = smartBorders $ Mirror tiled ||| Full ||| tiled
                     }
                     where
                        tiled = Tall 1 (3%100) (680%1000)
 
myKeys = Map.fromList $
    [ ((mod4Mask                    , xK_F2    ), spawn "gmrun")
    --, ((mod4Mask .|. shiftMask        , xK_t       ), spawn "thunar")
    , ((mod4Mask                    , xK_e       ), spawn "thunar")
    , ((mod4Mask                    , xK_o       ), spawn "urxvt -e screen")
    , ((mod4Mask                    , xK_F12   ), spawn "sudo shutdown -h now")
    , ((mod4Mask                    , xK_p     ), spawn "exe=`dmenu_path | dmenu -b -fn '-*-terminus-*-r-*-*-*-*-*-*-*-*-*-*' -nb '#000000' -nf '#FFFFFF'` && eval \"exec $exe\"") -- %! Launch dmenu
    , ((mod4Mask                    , xK_c       ), kill)
    ]

myManageHook = composeAll . concat $
                [ [ className =? c --> doFloat | c <- floats]
                , [ resource =? r --> doIgnore | r <- ignore]
                , [ resource =? "gecko" --> doF (W.shift "net") ]]
 where floats = ["MPlayer", "Gimp"]
       ignore = ["panel", "trayer"]

myPP h = defaultPP 
            { ppCurrent = wrap "^fg(#000000)^bg(#a6c292)^p(2)^i(/home/buttons/.bitmaps/has_win.xbm)" "^p(2)^fg()^bg()"
             , ppVisible = wrap "^bg(grey30)^fg(grey75)^p(2)" "^p(2)^fg()^bg()"
             , ppSep     = " ^fg(grey60)^r(3x3)^fg() "
             , ppLayout  = dzenColor "#80AA83" "" .
                           (\x -> case x of
                                    "Tall" -> "^i(/home/buttons/.bitmaps/tall.xbm)"
                                    "Mirror Tall" -> "^i(/home/buttons/.bitmaps/mtall.xbm)"
                                    "Full" -> "^i(/home/buttons/.bitmaps/full.xbm)"
                           )
             , ppTitle   = dzenColor "white" "" . wrap "< " " >" 
             , ppOutput   = hPutStrLn h
             }

I've gotta say, the darcs version makes configuration SO much more readable, not to mention less time-consuming.

I love that Config Thank you so much wink

Offline

#18 2007-12-11 00:41:25

buttons
Member
From: NJ, USA
Registered: 2007-08-04
Posts: 620

Re: xmonad Hacking Thread

JoyFM wrote:

Thank you so much wink

big_smile


Cthulhu For President!

Offline

#19 2007-12-11 20:09:31

strankan
Member
From: Sundsvall - Sweden
Registered: 2006-11-08
Posts: 97

Re: xmonad Hacking Thread

JoyFM wrote:
buttons wrote:

I kinda wonder if anyone didn't base theirs off Rob's, if simply for the excellent dynamicLog printer.

-- xmonad.hs
import XMonad
import XMonad.Layouts
import XMonad.Config                (defaultConfig)
import XMonad.Actions.RotView        ( rotView )
import XMonad.Hooks.DynamicLog        ( PP(..), dynamicLogWithPP, dzenColor, wrap, defaultPP )
import XMonad.Layout.NoBorders
import XMonad.Util.Run                (spawnPipe)
import Data.Bits

import XMonad.Operations
import qualified XMonad.StackSet as W 
import qualified Data.Map as Map
import Data.Ratio
import Graphics.X11.Xlib
import System.IO
 
statusBarCmd= "dzen2 -y 1010 -bg '#000000' -fg 'grey70' -sa c -fn '-*-terminus-*-*-*-*-12-*-*-*-*-*-iso8859' -e '' -ta l -w 600"
 
main = do din <- spawnPipe statusBarCmd
          xmonad $ defaultConfig
                     { borderWidth        = 1
                     , normalBorderColor  = "black"
                     , focusedBorderColor = "green"
                     , terminal           = "urxvt"
                     , workspaces         = ["main","net","dev"]
                                            ++ map show [4..9]
                     , defaultGaps        = [(30,14,0,0)]
                     , logHook            = dynamicLogWithPP $ myPP din
                     , manageHook          = myManageHook
                     , modMask            = mod4Mask
                     , keys               = \c -> myKeys `Map.union`
                                                  keys defaultConfig c
                     , layoutHook         = smartBorders $ Mirror tiled ||| Full ||| tiled
                     }
                     where
                        tiled = Tall 1 (3%100) (680%1000)
 
myKeys = Map.fromList $
    [ ((mod4Mask                    , xK_F2    ), spawn "gmrun")
    --, ((mod4Mask .|. shiftMask        , xK_t       ), spawn "thunar")
    , ((mod4Mask                    , xK_e       ), spawn "thunar")
    , ((mod4Mask                    , xK_o       ), spawn "urxvt -e screen")
    , ((mod4Mask                    , xK_F12   ), spawn "sudo shutdown -h now")
    , ((mod4Mask                    , xK_p     ), spawn "exe=`dmenu_path | dmenu -b -fn '-*-terminus-*-r-*-*-*-*-*-*-*-*-*-*' -nb '#000000' -nf '#FFFFFF'` && eval \"exec $exe\"") -- %! Launch dmenu
    , ((mod4Mask                    , xK_c       ), kill)
    ]

myManageHook = composeAll . concat $
                [ [ className =? c --> doFloat | c <- floats]
                , [ resource =? r --> doIgnore | r <- ignore]
                , [ resource =? "gecko" --> doF (W.shift "net") ]]
 where floats = ["MPlayer", "Gimp"]
       ignore = ["panel", "trayer"]

myPP h = defaultPP 
            { ppCurrent = wrap "^fg(#000000)^bg(#a6c292)^p(2)^i(/home/buttons/.bitmaps/has_win.xbm)" "^p(2)^fg()^bg()"
             , ppVisible = wrap "^bg(grey30)^fg(grey75)^p(2)" "^p(2)^fg()^bg()"
             , ppSep     = " ^fg(grey60)^r(3x3)^fg() "
             , ppLayout  = dzenColor "#80AA83" "" .
                           (\x -> case x of
                                    "Tall" -> "^i(/home/buttons/.bitmaps/tall.xbm)"
                                    "Mirror Tall" -> "^i(/home/buttons/.bitmaps/mtall.xbm)"
                                    "Full" -> "^i(/home/buttons/.bitmaps/full.xbm)"
                           )
             , ppTitle   = dzenColor "white" "" . wrap "< " " >" 
             , ppOutput   = hPutStrLn h
             }

I've gotta say, the darcs version makes configuration SO much more readable, not to mention less time-consuming.

I love that Config Thank you so much wink

Have to say I agree smile

Quick question though, I want to add date and time to the dzen-bar but I'm a complete novice when it comes to haskell. Can anyone point me in the right direction?

Offline

#20 2007-12-11 20:30:34

thayer
Fellow
From: Vancouver, BC
Registered: 2007-05-20
Posts: 1,560
Website

Re: xmonad Hacking Thread

strankan wrote:

Quick question though, I want to add date and time to the dzen-bar but I'm a complete novice when it comes to haskell. Can anyone point me in the right direction?

http://bbs.archlinux.org/viewtopic.php? … 51#p304851


thayer williams ~ cinderwick.ca

Offline

#21 2007-12-11 23:55:54

adekoba
Member
Registered: 2007-07-10
Posts: 128
Website

Re: xmonad Hacking Thread

would it be possible to create a grid layout that resembles wmii? As in the idea of seperate columns, where windows are tiled in their respective columns instead of adding them to some position in a "stack" (which is used as the default for xmonad and dwm).


abcdefghijklmnopqrstuvwxyz

Offline

#22 2007-12-12 00:28:04

thayer
Fellow
From: Vancouver, BC
Registered: 2007-05-20
Posts: 1,560
Website

Re: xmonad Hacking Thread

adekoba wrote:

would it be possible to create a grid layout that resembles wmii? As in the idea of seperate columns, where windows are tiled in their respective columns instead of adding them to some position in a "stack" (which is used as the default for xmonad and dwm).

I'm not sure what wmii's grid looks like, but this what the grid extension looks like for xmonad:

thumb-20071211-2442190826.png

Last edited by thayer (2010-12-05 23:22:05)


thayer williams ~ cinderwick.ca

Offline

#23 2007-12-12 01:53:43

adekoba
Member
Registered: 2007-07-10
Posts: 128
Website

Re: xmonad Hacking Thread

yeah, I tried it before posting and it still had that stack feel. It didn't allow me to have individual columns that were isolated from the stack. Oh well, I guess it probably doesn't, now that I think about it. The stack nature of xmonad is inherent in the code I bet.


abcdefghijklmnopqrstuvwxyz

Offline

#24 2007-12-12 04:00:57

Xilon
Member
Registered: 2007-01-01
Posts: 243

Re: xmonad Hacking Thread

I can't really recall any more, but didn't wmii allow you to have different layouts in each column? Like having a stack layout in the first column and a normal tiled in a second column? Afaik you can't do that in xmonad (yet, maybe if someone write a layout algorithm), but the default tiling really isn't bad:
200712121256061280x800srs7.th.png
Of course this is a 1280x800 screen, which is tiny. I'm not sure how I would like xmonad on my 1680x1050... There are a lot of layouts available though.

Offline

#25 2007-12-12 05:37:59

semdornus
Member
From: Tokyo
Registered: 2007-08-07
Posts: 47

Re: xmonad Hacking Thread

Xilon wrote:

Afaik you can't do that in xmonad (yet, maybe if someone write a layout algorithm)

Just a small FYI; you can do that in xmonad. See Combo, LayoutCombinators and/or LayoutScreens. Difficult to see, but in screenshot.

Last edited by semdornus (2007-12-12 05:39:45)

Offline

Board footer

Powered by FluxBB