Xmonad/General xmonad.hs config tips: Difference between revisions
m (→Do not show scratchpad workspace in status bar or dynamicLog: clarify subheading) |
m (→Skipping the Scratchpad workspace while using CycleWS: clarify where and (++)) |
||
Line 164: | Line 164: | ||
, ((modKey .|. controlMask .|. shiftMask, xK_Left), shiftAndView' Prev) | , ((modKey .|. controlMask .|. shiftMask, xK_Left), shiftAndView' Prev) | ||
] | ] | ||
-- Make sure to put any where clause after your last list of key bindings* | |||
where notSP = (return $ ("SP" /=) . W.tag) :: X (WindowSpace -> Bool) | where notSP = (return $ ("SP" /=) . W.tag) :: X (WindowSpace -> Bool) | ||
-- | any workspace but scratchpad | -- | any workspace but scratchpad | ||
Line 174: | Line 176: | ||
fmap (.scratchpadFilterOutWorkspace) getSortByIndex | fmap (.scratchpadFilterOutWorkspace) getSortByIndex | ||
-- * | -- *For example, you could not (++) another list here | ||
-- | |||
-- | -- ------------------------------------------------------------------------ | ||
-- If notSP or some variant of the shiftAndView functions isn't needed, but | |||
-- you do want to use shiftTo or moveTo, delete notSP and use a version of: | |||
-- ((modKey, xK_Right ), moveTo Next . WSIs . return $ ("SP" /=) . W.tag) | |||
</haskell> | </haskell> | ||
Also of course, the where definitions, or X () actions bound here can be moved out to | Also of course, the where definitions, or X () actions bound here can be moved out to |
Revision as of 20:49, 3 February 2009
This document assumes you're running >= XMonad-0.8.
It describes general tips for configuring xmonad.hs, for example "How to make window X float by default" and others. If you can't find what you're searching for, you may want to look at the Config archive or ask for help on #xmonad@irc.freenode.net.
Also useful, for an overview of how to configure bindings and hooks, and (somewhat out of date) summary of xmonad-contrib extensions, see XMonad.Doc.Extending.
Please add what you found useful, and of course improving existing tips or adding alternatives is highly appreciated!
Making window float by default, or send it to specific workspace
This example shifts Rythmbox to workspace "=" and XDvi to "7:dvi", floats Xmessage, and uses manageDocks to leave gaps for status bars automatically. All this is combined with the default xmonad manageHook. This step-by-step tutorial covers initially setting up a manageHook, too.
-- module imports and other top level definitions
myManageHook = composeAll
[ className =? "Rhythmbox" --> doShift "="
, className =? "XDvi" --> doShift "7:dvi"
, className =? "Xmessage" --> doFloat
, manageDocks
]
main = xmonad $ defaultConfig
{
-- terminal, modMask, keys, etc.
-- bind a key to 'sendMessage ToggleStruts' to toggle statusbar
, manageHook = manageHook defaultConfig <+> myManageHook -- uses default too
-- layoutHook, logHook, etc.
}
This example sends Firefox to workspace "web" when it starts. Gajim gets sent to workspace "jabber".Finally, it floats Firefox dialog windows, and makes Gajim and Xmessage float, too.
myManageHook = composeAll . concat $
[ [ className =? "Firefox-bin" --> doShift "web" ]
, [ className =? "Gajim.py" --> doShift "jabber" ]
, [(className =? "Firefox" <&&> resource =? "Dialog") --> doFloat]
, [ className =? c --> doFloat | c <- myFloats ]
]
where myFloats = ["Gajim.py", "Xmessage"]
Here's another example, using both classes and titles:
myManageHook :: ManageHook
myManageHook = composeAll . concat $
[ [ title =? t --> doFloat | t <- myTitleFloats]
, [ className =? c --> doFloat | c <- myClassFloats ] ]
where
myTitleFloats = ["Transferring"] -- for the KDE "open link" popup from konsole
myClassFloats = ["Pinentry"] -- for gpg passphrase entry
See the FAQ about using xprop to get the properties of windows.
See also the documentation for ManageHook.
Making windows unfloat
A related task is - how do I unfloat windows of a particular class or name? Well, as before, we need to set up a managehook, and then we write a simple function which duplicates the mod-t functionality of unfloating (but with a different type):
myManageHook :: ManageHook
myManageHook = composeAll [ className =? "defcon.bin.x86" --> unfloat,
className =? "Darwinia" --> unfloat ]
<+> manageDocks
where unfloat = ask >>= doF . W.sink
Ignoring a client (or having it sticky)
You can have the position and geometry of a client window respected, and have that window be sticky, by ignoring it when it is created:
main = xmonad $ defaultConfig
{
....
, manageHook = manageHook defaultConfig
<+>
(className =? "XClock" --> doIgnore)
...
}
Would let xclock be sticky, and have its geometry respected.
Adding your own keybindings
This adds Mod-x keybinding for running xlock.
import qualified Data.Map as M
-- skipped
main = xmonad $ defaultConfig {
--
, keys = \c -> mykeys c `M.union` keys defaultConfig c }
--
}
where
mykeys (XConfig {modMask = modm}) = M.fromList $
[ ((modm , xK_x), spawn "xlock") ]
For a list of the identifiers used for various keys, see Graphics.X11.Types and ExtraTypes.
This is also described in [1]
Adding your own mouse bindings
Adding your own mouse bindings is explained in [2]
If you have a mouse with more than 5 buttons you can simply use '6' instead of 'button6' which isn't defined.
e.g. with EZConfig:
,((0, 6), (\w -> focus w >> windows W.swapMaster))
Skipping the Scratchpad workspace while using CycleWS
The Actions.Plane and Actions.CycleWS extensions allow many ways to navigate workspaces, or shift windows to other workspaces. Plane is easier to set up, CycleWS allows nearly any behaviour you'd ever want. The Util.Scratchpad module provides a configurable floating terminal that is easily shifted to the current workspace or banished to its own "SP" workspace. Most people want the "SP" tag ignored during workspace navigation.
Here's one way to do that with Actions.CycleWS, ready to be customized, for example to use HiddenEmptyWSs instead of HiddenNonEmptyWSs, etc.
Note that notSP
is defined in the where clause of this example. It is
just another name for (return $ ("SP" /=) . W.tag) :: X (WindowSpace -> Bool)
Likewise, for getSortByIndexNoSP
, look in where clause.
--
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig -- optional, but helpful
import Xmonad.Actions.CycleWS
import XMonad.Util.Scratchpad
import XMonad.Util.WorkspaceCompare
modKey = mod4Mask
-- other keybindings [ ]
++
-- focus /any/ workspace except scratchpad, even visible
[ ((modKey, xK_Right ), moveTo Next (WSIs notSP))
, ((modKey, xK_Left ), moveTo Prev (WSIs notSP))
-- move window to /any/ workspace except scratchpad
, ((modKey .|. shiftMask, xK_Right ), shiftTo Next (WSIs notSP))
, ((modKey .|. shiftMask, xK_Left ), shiftTo Prev (WSIs notSP))
-- focus HiddenNonEmpty wss except scratchpad
, ((modKey .|. controlMask , xK_Right),
windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Next HiddenNonEmptyWS 1)
, ((modKey .|. controlMask , xK_Left),
windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Prev HiddenNonEmptyWS 1)
-- move window to HiddenNonEmpty wss except scratchpad
, ((modKey .|. shiftMask, xK_Right),
windows . W.shift =<< findWorkspace getSortByIndexNoSP Next HiddenNonEmptyWS 1)
, ((modKey .|. shiftMask, xK_Left),
windows . W.shift =<< findWorkspace getSortByIndexNoSP Prev HiddenNonEmptyWS 1)
-- move window to and focus HiddenNonEmpty wss except scratchpad
, ((modKey .|. controlMask .|. shiftMask, xK_Right), shiftAndView' Next)
, ((modKey .|. controlMask .|. shiftMask, xK_Left), shiftAndView' Prev)
]
-- Make sure to put any where clause after your last list of key bindings*
where notSP = (return $ ("SP" /=) . W.tag) :: X (WindowSpace -> Bool)
-- | any workspace but scratchpad
shiftAndView dir = findWorkspace getSortByIndex dir (WSIs notSP) 1
>>= \t -> (windows . W.shift $ t) >> (windows . W.greedyView $ t)
-- | hidden, non-empty workspaces less scratchpad
shiftAndView' dir = findWorkspace getSortByIndexNoSP dir HiddenNonEmptyWS 1
>>= \t -> (windows . W.shift $ t) >> (windows . W.greedyView $ t)
getSortByIndexNoSP =
fmap (.scratchpadFilterOutWorkspace) getSortByIndex
-- *For example, you could not (++) another list here
-- ------------------------------------------------------------------------
-- If notSP or some variant of the shiftAndView functions isn't needed, but
-- you do want to use shiftTo or moveTo, delete notSP and use a version of:
-- ((modKey, xK_Right ), moveTo Next . WSIs . return $ ("SP" /=) . W.tag)
Also of course, the where definitions, or X () actions bound here can be moved out to top level definitions if you want to use them repeatedly.
Do not show scratchpad workspace in status bar or dynamicLog
You can also use fmap (.scratchpadFilterOutWorkspace)
on a ppSort
in your logHook.
, logHook = dynamicLogWithPP defaultPP {
ppSort = fmap (.scratchpadFilterOutWorkspace) $ ppSort defaultPP
or
import XMonad.Util.WorkspaceCompare
-- skipped
, logHook = dynamicLogWithPP defaultPP {
ppSort = fmap (.scratchpadFilterOutWorkspace) getSortByTag
Sharing a configuration across different hosts
It is possible to have different parts of the configuration file vary from one host to another, without needing a different config file for each host. Here is an example from my configuration file:
import System.Posix.Unistd
-- skipped
main = do
host <- fmap nodeName getSystemID
-- equivalent, and arguably more readable is
-- host <- getSystemID >>= nodeName
xmonad $ defaultConfig
{ terminal = "rxvt"
, modMask = (if host == "janice" then
mod1Mask .|. controlMask
else
mod4Mask)
-- also can pass hostname to other functions if needed
, logHook = dynamicLogWithPP $ myPP host
}
myPP hostname =
if hostname == "janice" then dzenPP else xmobarPP
Binding keys to a specific layout
Sometimes people want to bind a key to a particular layout, rather than having to cycle through the available layouts:
You can do this using the JumpToLayout message from the XMonad.Layout.LayoutCombinators extension module. For example:
import XMonad hiding ( (|||) ) -- don't use the normal ||| operator
import XMonad.Layout.LayoutCombinators -- use the one from LayoutCombinators instead
import XMonad.Util.EZConfig -- add keybindings easily
main = xmonad myConfig
myConfig = defaultConfig {
--
layoutHook = tall ||| Mirror tall ||| Full
--
} `additionalKeysP`
[ ("M-<F1>", sendMessage $ JumpToLayout "Tall")
, ("M-<F2>", sendMessage $ JumpToLayout "Mirror Tall")
, ("M-<F3>", sendMessage $ JumpToLayout "Full")
]
tall = Tall 1 (3/100) (1/2)
Using local state in the config file
As the xmonad config file is really just the entry point to the entire program, you can do arbitrary IO effects before running xmonad. Including initialising mutable "global" state. That state could even be made persistent , independent of xmonad's built-in persistence (by writing it to a file on mod-q).
Here's an example where we store the layouts "IncMaster" value in a local mutable variable, so that we can provide a key binding that takes that value to compute an offset.
import XMonad
import XMonad.Util.EZConfig
import Data.IORef
import XMonad.Actions.FocusNth
main = do
offset <- newIORef 1
xmonad $ defaultConfig
`additionalKeys`
([ ((modMask defaultConfig, xK_comma ),
do io $ modifyIORef offset (\i -> max 0 (i-1))
sendMessage (IncMasterN (-1))
)
, ((modMask defaultConfig, xK_period ),
do io $ modifyIORef offset (+1)
sendMessage (IncMasterN 1)
) -- %! Expand the master area
] ++ [((modMask defaultConfig .|. shiftMask, k), do
n <- io $ readIORef offset
focusNth (i+n))
| (i, k) <- zip [0 .. 8] [xK_1 ..]]
)
Note IORef is allocated at startup.