[xmonad] For Darcs-Head: How to change Keybindings

Spencer Janssen sjanssen at cse.unl.edu
Wed Nov 14 03:36:01 EST 2007


On Monday 12 November 2007 08:31:14 Dominik Bruhn wrote:
> Hy,
> thanks all for your answers, I tried the following Config (based uppon
> the one from Sjannen in the wiki:
> See attachment
>
> The problem is the following error-message uppon compiling:
> ---- snip -----
> xmonad.hs:18:1:
>     Ambiguous type variable `m' in the constraint:
>       `Monad m' arising from use of `return' at xmonad.hs:18:1-6
>     Possible cause: the monomorphism restriction applied to the following:
>       dominikConfig :: m (XConfig (Choose Tall
> 					  (Choose (Mirror Tall) Full)))
> 	(bound at xmonad.hs:17:0)
>     Probable fix: give these definition(s) an explicit type signature
> 		  or use -fno-monomorphism-restriction
> --------------
>
> Who can help me and give me a hint how to fix this error?
>
> Thanks
> Dominik

Attached is a file that you can save to ~/.xmonad/xmonad.hs.


Cheers,
Spencer Janssen

-------------- next part --------------
import XMonad

import XMonad.Layouts
import XMonad.Operations
import XMonad.ManageHook
import qualified XMonad.StackSet as W
import Data.Bits ((.|.))
import qualified Data.Map as M
import System.Exit
import Graphics.X11.Xlib


import XMonad.Hooks.DynamicLog

main = xmonad $ defaultConfig
		{	workspaces = myWorkspaces,
			modMask = mod4Mask,
			defaultGaps = [(13,0,0,0)],
			logHook = dynamicLog,
			terminal = "urxvtc",
		 	manageHook = myManageHook,
			keys = \c -> myKeys c `M.union` keys defaultConfig c
		}
	where
		myWorkspaces = ["1", "web", "mp3"] ++ map show [4 .. 8 :: Int] ++ ["im"]
		myKeys (XConfig {modMask = modm}) = M.fromList $
			 [((modm, xK_p ),  spawn "exe=`dmenu_path | dmenu -fn -*-fixed-*-r-*-*-10` && eval \"exec $exe\"")]
		myManageHook = composeAll . concat $
			[ [ className =? c --> doFloat | c <- floats]
			, [ resource =? r --> doIgnore | r <- ignore]
			, [ className =? "Firefox-bin" --> doF (W.shift "web") ]
			, [ resource =? "pidgin" --> doF (W.shift "im") ]
			, [ resource =? "Eclipse" --> doF (W.shift "4") ]
			, [ resource =? "eclipse" --> doF (W.shift "4") ]
			]
			where
				floats = ["MPlayer", "Gimp", "Dia"]
				ignore = ["gnome-panel", "desktop_window", "kicker", "kdesktop", "panel"]


More information about the xmonad mailing list