aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Config/Droundy.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-11-12 18:20:32 +0100
committerDavid Roundy <droundy@darcs.net>2007-11-12 18:20:32 +0100
commit538b4acedaf243bea1110aafec9bb2a58877982a (patch)
tree281564f5dae233c0f291617fcd3aaa02f99a2d3a /XMonad/Config/Droundy.hs
parent3a6bd93ba054c34acaf7fbb006d5b814da683a89 (diff)
downloadXMonadContrib-538b4acedaf243bea1110aafec9bb2a58877982a.tar.gz
XMonadContrib-538b4acedaf243bea1110aafec9bb2a58877982a.tar.xz
XMonadContrib-538b4acedaf243bea1110aafec9bb2a58877982a.zip
prune Droundy.hs.
darcs-hash:20071112172032-72aca-dd624f0434e4c10a7d3697a7a1546d33f5b94a27.gz
Diffstat (limited to 'XMonad/Config/Droundy.hs')
-rw-r--r--XMonad/Config/Droundy.hs26
1 files changed, 2 insertions, 24 deletions
diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs
index 8e9f3c1..856db86 100644
--- a/XMonad/Config/Droundy.hs
+++ b/XMonad/Config/Droundy.hs
@@ -4,14 +4,6 @@
-- Copyright : (c) Spencer Janssen 2007
-- License : BSD3-style (see LICENSE)
--
--- Maintainer : dons@galois.com
--- Stability : stable
--- Portability : portable
---
--- This module specifies configurable defaults for xmonad. If you change
--- values here, be sure to recompile and restart (mod-q) xmonad,
--- for the changes to take effect.
---
------------------------------------------------------------------------
module XMonad.Config.Droundy where
@@ -19,8 +11,8 @@ module XMonad.Config.Droundy where
--
-- Useful imports
--
-import XMonad hiding (keys,mouseBindings)
-import qualified XMonad (keys,mouseBindings)
+import XMonad hiding (keys)
+import qualified XMonad (keys)
import XMonad.Config ( defaultConfig )
import XMonad.Layouts hiding ( (|||) )
@@ -124,19 +116,6 @@ keys x = M.fromList $
++
zip (zip (repeat (modMask x .|. shiftMask)) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
--- | Mouse bindings: default actions bound to mouse events
---
-mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
-mouseBindings x = M.fromList $
- -- mod-button1 %! Set the window to floating mode and move by dragging
- [ ((modMask x, button1), (\w -> focus w >> mouseMoveWindow w))
- -- mod-button2 %! Raise the window to the top of the stack
- , ((modMask x, button2), (\w -> focus w >> windows W.swapMaster))
- -- mod-button3 %! Set the window to floating mode and resize by dragging
- , ((modMask x, button3), (\w -> focus w >> mouseResizeWindow w))
- -- you may also bind events to the mouse scroll wheel (button4 and button5)
- ]
-
config = defaultConfig
{ borderWidth = 1 -- Width of the window border in pixels.
, XMonad.workspaces = ["1:mutt","2:iceweasel"]
@@ -149,7 +128,6 @@ config = defaultConfig
, focusedBorderColor = "#00ff00" -- Border color for focused windows.
, XMonad.modMask = mod1Mask
, XMonad.keys = keys
- , XMonad.mouseBindings = mouseBindings
}
where mytab = tabbed shrinkText defaultTConf