Difference between revisions of "Xmonad/General xmonad.hs config tips"

From HaskellWiki
Jump to navigation Jump to search
(add haskell tags)
Line 8: Line 8:
   
 
This example sends Firefox to workspace "web" by default, makes Gajim float and sends it to webspace "jabber" and Xmessage is floating by default, too.
 
This example sends Firefox to workspace "web" by default, makes Gajim float and sends it to webspace "jabber" and Xmessage is floating by default, too.
  +
<haskell>
 
 
myManageHook :: ManageHook
 
myManageHook :: ManageHook
 
myManageHook = composeAll . concat $
 
myManageHook = composeAll . concat $
Line 22: Line 22:
 
'''...'''
 
'''...'''
 
}
 
}
  +
</haskell>
 
 
== Ignoring a client (or having it sticky) ==
 
== Ignoring a client (or having it sticky) ==
   
 
You can have the position and geometry of a client window respected, and have that window
 
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:
 
be sticky, by ignoring it when it is created:
  +
<haskell>
 
 
main = xmonad $ defaultConfig
 
main = xmonad $ defaultConfig
 
{
 
{
Line 36: Line 36:
 
...
 
...
 
}
 
}
  +
</haskell>
 
 
Would let xclock be sticky, and have its geometry respected.
 
Would let xclock be sticky, and have its geometry respected.
   
Line 42: Line 42:
   
 
This adds Mod-x keybinding for running ''xlock''.
 
This adds Mod-x keybinding for running ''xlock''.
  +
<haskell>
 
import qualified Data.Map as M
 
import qualified Data.Map as M
   
Line 55: Line 56:
 
mykeys (XConfig {modMask = modm}) = M.fromList $
 
mykeys (XConfig {modMask = modm}) = M.fromList $
 
[ ((modm , xK_x), spawn "xlock") ]
 
[ ((modm , xK_x), spawn "xlock") ]
  +
</haskell>
 
 
For a list of the identifiers used for various keys, see
 
For a list of the identifiers used for various keys, see
 
[http://hackage.haskell.org/packages/archive/X11/1.4.1/doc/html/Graphics-X11-Types.html].
 
[http://hackage.haskell.org/packages/archive/X11/1.4.1/doc/html/Graphics-X11-Types.html].
Line 78: Line 79:
   
 
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:
 
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:
  +
<haskell>
 
 
import System.Posix.Unistd
 
import System.Posix.Unistd
   
Line 95: Line 96:
 
else
 
else
 
mod4Mask)}
 
mod4Mask)}
  +
</haskell>
 
 
== Binding keys to a specific layout ==
 
== Binding keys to a specific layout ==
   
Line 138: Line 139:
   
 
<haskell>
 
<haskell>
 
 
 
 
import XMonad
 
import XMonad
 
import XMonad.Util.EZConfig
 
import XMonad.Util.EZConfig
Line 165: Line 163:
 
| (i, k) <- zip [0 .. 8] [xK_1 ..]]
 
| (i, k) <- zip [0 .. 8] [xK_1 ..]]
 
)
 
)
 
 
</haskell>
 
</haskell>
   

Revision as of 07:28, 10 December 2008


This site is for 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.

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 sends Firefox to workspace "web" by default, makes Gajim float and sends it to webspace "jabber" and Xmessage is floating by default, too.

   myManageHook :: ManageHook
   myManageHook = composeAll . concat $
       [ [ className =? c --> doFloat | c <- myFloats ]
       , [ className =? "Firefox-bin" --> doF (W.shift "web" ) ]
       , [ className =? "Gajim.py" --> doF (W.shift "jabber" ) ] ]
       where myFloats = ["Gajim.py", "Xmessage"]

   main = xmonad $ defaultConfig
   {
   '''....'''
   , manageHook    = manageHook defaultConfig <+> myManageHook
   '''...'''
   }

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

   '''....'''

   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 [1].

This is also described in [2]

Adding your own mouse bindings

Adding your own mouse bindings is explained in [3]

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


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

    .
    .
    .

    main = do
        host <- fmap nodeName getSystemID
        -- equivalent, and arguably more readable is
        -- host <- getSystemID >>= return . nodeName
        xmonad $ defaultConfig
          { terminal           = "rxvt"
          , modMask            = (if host == "janice" then
                                    mod1Mask .|. controlMask
                                  else
                                    mod4Mask)}

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.