[xmonad] Basic configuration : Config.Gnome + some more keys

Henrique G. Abreu hgabreu at gmail.com
Sun Sep 13 20:51:01 EDT 2009


>
> I will have to search a little more for this part, because the keymap
> I'm using
> does not offer direct access to digits: that's why I bind Fn keys.
>

It compiles, but I have not tested it and I have no clue if its going to
work.
just copied some examples from config archive, I don't really know what I'm
doing ;)

import XMonad
import XMonad.Actions.CycleWS
import XMonad.Config.Gnome
import XMonad.Util.EZConfig
import qualified XMonad.StackSet as W

main = do
    xmonad $ gnomeConfig
        { modMask = mod4Mask
        } `additionalKeysP` (extraKeys gnomeConfig)

extraKeys conf =
    [ ("M-<L>", prevWS)
    , ("M-<R>", nextWS)
    , ("M-S-<L>", shiftToPrev)
    , ("M-S-<R>", shiftToNext)
    ]
    ++
    [ (m ++ (show k) ++ ">", windows $ f i)
        | (i, k) <- zip (XMonad.workspaces conf) [1 .. 9]
        , (f, m) <- [(W.greedyView, "M-<F"), (W.shift, "M-S-<F")]
    ]

Regards,
Henrique G. Abreu
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/xmonad/attachments/20090913/4b25cdbf/attachment.html


More information about the xmonad mailing list