aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-05 07:00:36 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-05 07:00:36 +0100
commit79584d0940895c4aea161ea079951ab64dd78676 (patch)
tree0231a22452d83a15f992feba3d8f05ab0e58a44a /XMonad
parent63ba747da073e414fa716683ee331ed8c0eccba6 (diff)
downloadXMonadContrib-79584d0940895c4aea161ea079951ab64dd78676.tar.gz
XMonadContrib-79584d0940895c4aea161ea079951ab64dd78676.tar.xz
XMonadContrib-79584d0940895c4aea161ea079951ab64dd78676.zip
-Wall police
darcs-hash:20071105060036-a5988-67e0d7402a87ae5d672e5b556a5a03caf6ad5559.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Actions/Submap.hs2
-rw-r--r--XMonad/Config/Sjanssen.hs24
-rw-r--r--XMonad/Layout/Spiral.hs1
-rw-r--r--XMonad/Prompt/Shell.hs2
4 files changed, 13 insertions, 16 deletions
diff --git a/XMonad/Actions/Submap.hs b/XMonad/Actions/Submap.hs
index 98d44c6..4e1d3a5 100644
--- a/XMonad/Actions/Submap.hs
+++ b/XMonad/Actions/Submap.hs
@@ -20,7 +20,7 @@ module XMonad.Actions.Submap (
import Control.Monad.Reader
-import XMonad
+import XMonad hiding (keys)
import XMonad.Operations (cleanMask)
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
diff --git a/XMonad/Config/Sjanssen.hs b/XMonad/Config/Sjanssen.hs
index 76d7e1f..75969bd 100644
--- a/XMonad/Config/Sjanssen.hs
+++ b/XMonad/Config/Sjanssen.hs
@@ -11,7 +11,6 @@ import XMonad.Hooks.DynamicLog
import XMonad.Prompt
import XMonad.Prompt.Shell
-import Data.Ratio
import Data.Bits
import qualified Data.Map as M
import Graphics.X11
@@ -20,23 +19,22 @@ sjanssenConfig :: XConfig
sjanssenConfig = defaultConfig
{ defaultGaps = [(15,0,0,0)]
, terminal = "urxvt"
- , workspaces = ["irc", "web"] ++ map show [3..7] ++ ["mail", "im"]
+ , workspaces = ["irc", "web"] ++ map show [3 .. 7 :: Int] ++ ["mail", "im"]
, logHook = dynamicLogWithPP sjanssenPP
, modMask = mod4Mask
- , mouseBindings = \(XConfig {modMask = modMask}) -> M.fromList $
- [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
- , ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
- , ((modMask .|. shiftMask, button1), (\w -> focus w >> mouseResizeWindow w)) ]
+ , mouseBindings = \(XConfig {modMask = modm}) -> M.fromList $
+ [ ((modm, button1), (\w -> focus w >> mouseMoveWindow w))
+ , ((modm, button2), (\w -> focus w >> windows W.swapMaster))
+ , ((modm.|. shiftMask, button1), (\w -> focus w >> mouseResizeWindow w)) ]
, keys = \c -> mykeys c `M.union` keys defaultConfig c
, layoutHook = Layout (smartBorders (tiled ||| Mirror tiled ||| Full ||| tabbed shrinkText defaultTConf))
}
where
- mykeys (XConfig {modMask = modMask}) = M.fromList $
- [((modMask, xK_p ), shellPrompt myPromptConfig)]
- -- default tiling algorithm partitions the screen into two panes
tiled = Tall 1 0.5 0.03
-myPromptConfig = defaultXPConfig
- { position = Top
- , promptBorderWidth = 0
- }
+ mykeys (XConfig {modMask = modm}) = M.fromList $
+ [((modm, xK_p ), shellPrompt myPromptConfig)]
+
+ myPromptConfig = defaultXPConfig
+ { position = Top
+ , promptBorderWidth = 0 }
diff --git a/XMonad/Layout/Spiral.hs b/XMonad/Layout/Spiral.hs
index 013a017..ae82ad9 100644
--- a/XMonad/Layout/Spiral.hs
+++ b/XMonad/Layout/Spiral.hs
@@ -24,7 +24,6 @@ module XMonad.Layout.Spiral (
) where
import Graphics.X11.Xlib
-import XMonad.Operations
import Data.Ratio
import XMonad
import XMonad.Layouts
diff --git a/XMonad/Prompt/Shell.hs b/XMonad/Prompt/Shell.hs
index dfbfb09..b1fef6b 100644
--- a/XMonad/Prompt/Shell.hs
+++ b/XMonad/Prompt/Shell.hs
@@ -28,7 +28,7 @@ import Data.List
import System.Directory
import System.IO
import XMonad.Util.Run
-import XMonad
+import XMonad hiding (config)
import XMonad.Prompt
-- $usage