Basic configuration : Config.Gnome + some more keys

Hello, I'm a happy user of xmonad since about 1 year. But I don't know haskell language at all. (I know: I should learn, but… lack of time, and also happy OCaml programmer). My problem: I just installed a brand new computer. Then xmonad, and I use it with Gnome. My xmonad.hs is: import XMonad import XMonad.Config.Gnome main = xmonad gnomeConfig { modMask = mod4Mask } I now want to integrate some more key bindings, but I'm not able to put together all the informations gathered from the documentation. Here are the binding I'd like to add: -- import XMonad.Actions.CycleWS -- import qualified XMonad.StackSet as S ------------------------------------------------------------------------ -- Key bindings. Add, modify or remove key bindings here. -- -- myKeys conf = -- -- -- -- -- mod-[1..9], Switch to workspace N -- -- mod-shift-[1..9], Move client to workspace N -- -- -- [((modMask, k), windows $ S.greedyView i) -- | (i, k) <- zip (XMonad.workspaces conf) [xK_F1 .. xK_F9] -- -- , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] -- ] -- ++ -- [ ((modMask, xK_Left ), prevWS ) -- , ((modMask, xK_Right ), nextWS ) -- , ((modMask .|. shiftMask, xK_Left ), shiftToPrev ) -- , ((modMask .|. shiftMask, xK_Right ), shiftToNext )] First problem: the last 2 lines have a problem. Couldn't match expected type `XConfig l -> KeyMask' against inferred type `KeyMask' In the second argument of `(.|.)', namely `shiftMask' In the expression: modMask .|. shiftMask In the expression: (modMask .|. shiftMask, xK_Left) Second problem: how to integrate myKeys with Config.Gnome bindings ? Thanks in advance Matt

Matthieu,
I'm new to xmonad too (half a year) and also know nothing of haskell, but I
think I can help you.
The easiest way I found to add my own key bindings is using EZConfig
additionalKeysP, like this:
import XMonad
import XMonad.Actions.CycleWS
import XMonad.Config.Gnome
import XMonad.Util.EZConfig
main = do
xmonad $ gnomeConfig
{ modMask = mod4Mask
} `additionalKeysP`
[ ("M-<L>", prevWS )
, ("M-<R>", nextWS )
, ("M-S-<L>", shiftToPrev)
, ("M-S-<R>", shiftToNext)
]
If I understood right, this should do what you want.
The mod-[1..9] and mod-shift-[1..9] are already part of the default
bidingshttp://haskell.org/sitewiki/images/b/b8/Xmbindings.png
.
Regards,
Henrique G. Abreu
On Sat, Sep 12, 2009 at 10:50, Matthieu Dubuget
Hello,
I'm a happy user of xmonad since about 1 year. But I don't know haskell language at all. (I know: I should learn, but… lack of time, and also happy OCaml programmer).
My problem:
I just installed a brand new computer. Then xmonad, and I use it with Gnome.
My xmonad.hs is:
import XMonad import XMonad.Config.Gnome main = xmonad gnomeConfig { modMask = mod4Mask }
I now want to integrate some more key bindings, but I'm not able to put together all the informations gathered from the documentation.
Here are the binding I'd like to add:
-- import XMonad.Actions.CycleWS -- import qualified XMonad.StackSet as S
------------------------------------------------------------------------ -- Key bindings. Add, modify or remove key bindings here. -- -- myKeys conf = -- -- -- -- -- mod-[1..9], Switch to workspace N -- -- mod-shift-[1..9], Move client to workspace N -- -- -- [((modMask, k), windows $ S.greedyView i) -- | (i, k) <- zip (XMonad.workspaces conf) [xK_F1 .. xK_F9] -- -- , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] -- ] -- ++ -- [ ((modMask, xK_Left ), prevWS ) -- , ((modMask, xK_Right ), nextWS ) -- , ((modMask .|. shiftMask, xK_Left ), shiftToPrev ) -- , ((modMask .|. shiftMask, xK_Right ), shiftToNext )]
First problem: the last 2 lines have a problem.
Couldn't match expected type `XConfig l -> KeyMask' against inferred type `KeyMask' In the second argument of `(.|.)', namely `shiftMask' In the expression: modMask .|. shiftMask In the expression: (modMask .|. shiftMask, xK_Left)
Second problem: how to integrate myKeys with Config.Gnome bindings ?
Thanks in advance
Matt _______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad

Henrique G. Abreu a écrit :
Matthieu,
I'm new to xmonad too (half a year) and also know nothing of haskell, but I think I can help you. The easiest way I found to add my own key bindings is using EZConfig additionalKeysP, like this:
import XMonad import XMonad.Actions.CycleWS import XMonad.Config.Gnome import XMonad.Util.EZConfig
main = do xmonad $ gnomeConfig { modMask = mod4Mask } `additionalKeysP` [ ("M-<L>", prevWS ) , ("M-<R>", nextWS ) , ("M-S-<L>", shiftToPrev) , ("M-S-<R>", shiftToNext) ]
If I understood right, this should do what you want.
Exactly! Thanks a lot Henrique.
The mod-[1..9] and mod-shift-[1..9] are already part of the default bidings http://haskell.org/sitewiki/images/b/b8/Xmbindings.png.
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. Salutations Matt

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-

I ended with this, but failed when I tried to turn my enumeration into comprehension… import XMonad import XMonad.Config.Gnome import XMonad.Actions.CycleWS import XMonad.Util.EZConfig import qualified XMonad.StackSet as S main = do xmonad $ gnomeConfig { modMask = mod4Mask } `additionalKeys` [ ((mod4Mask, xK_Left ), prevWS ) , ((mod4Mask, xK_Right ), nextWS ) , ((mod4Mask .|. shiftMask, xK_Left ), shiftToPrev ) , ((mod4Mask .|. shiftMask, xK_Right ), shiftToNext ) , ((mod4Mask , xK_F1 ), windows $ S.greedyView "1") , ((mod4Mask , xK_F2 ), windows $ S.greedyView "2") , ((mod4Mask , xK_F3 ), windows $ S.greedyView "3") , ((mod4Mask , xK_F4 ), windows $ S.greedyView "4") , ((mod4Mask , xK_F5 ), windows $ S.greedyView "5") , ((mod4Mask , xK_F6 ), windows $ S.greedyView "6") , ((mod4Mask , xK_F7 ), windows $ S.greedyView "7") , ((mod4Mask , xK_F8 ), windows $ S.greedyView "8") , ((mod4Mask , xK_F9 ), windows $ S.greedyView "9") , ((mod4Mask .|. shiftMask, xK_F1 ), windows $ S.shift "1") , ((mod4Mask .|. shiftMask, xK_F2 ), windows $ S.shift "2") , ((mod4Mask .|. shiftMask, xK_F3 ), windows $ S.shift "3") , ((mod4Mask .|. shiftMask, xK_F4 ), windows $ S.shift "4") , ((mod4Mask .|. shiftMask, xK_F5 ), windows $ S.shift "5") , ((mod4Mask .|. shiftMask, xK_F6 ), windows $ S.shift "6") , ((mod4Mask .|. shiftMask, xK_F7 ), windows $ S.shift "7") , ((mod4Mask .|. shiftMask, xK_F8 ), windows $ S.shift "8") , ((mod4Mask .|. shiftMask, xK_F9 ), windows $ S.shift "9") ] Salutations Matt

The default configuration already has most of those keybindings! Try this. ~d import XMonad import XMonad.Config.Gnome import XMonad.Actions.CycleWS import XMonad.Util.EZConfig import qualified XMonad.StackSet as S main = do xmonad $ gnomeConfig { modMask = mod4Mask } `additionalKeys` [ ((mod4Mask, xK_Left ), prevWS ) , ((mod4Mask, xK_Right ), nextWS ) , ((mod4Mask .|. shiftMask, xK_Left ), shiftToPrev ) , ((mod4Mask .|. shiftMask, xK_Right ), shiftToNext ) ]
participants (3)
-
Henrique G. Abreu
-
Matthieu Dubuget
-
wagnerdm@seas.upenn.edu