summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorSpencer Janssen <spencerjanssen@gmail.com>2010-02-14 03:57:50 +0100
committerSpencer Janssen <spencerjanssen@gmail.com>2010-02-14 03:57:50 +0100
commite68fe01a84582d5e5a94d2eab8c914484ae81dd7 (patch)
tree7cc0b7ede3b1efed764eda7eaa5e778b9c7350c7
parentb51abc61705e6ec421c68e2f86b97a78b42f5c1e (diff)
downloadmetatile-e68fe01a84582d5e5a94d2eab8c914484ae81dd7.tar
metatile-e68fe01a84582d5e5a94d2eab8c914484ae81dd7.zip
Various clean-ups suggested by HLint
Ignore-this: ccaa6e774f2f8169e6083eddcffe31b6 darcs-hash:20100214025750-25a6b-c15d6ca0ac2f1dc7d3da2f7b311584df7f96dffd
-rw-r--r--XMonad/Config.hs14
-rw-r--r--XMonad/Core.hs2
-rw-r--r--XMonad/Layout.hs6
-rw-r--r--XMonad/Operations.hs15
-rw-r--r--XMonad/StackSet.hs4
5 files changed, 20 insertions, 21 deletions
diff --git a/XMonad/Config.hs b/XMonad/Config.hs
index abc9bb8..b092af0 100644
--- a/XMonad/Config.hs
+++ b/XMonad/Config.hs
@@ -220,15 +220,15 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
-- | Mouse bindings: default actions bound to mouse events
--
mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
-mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
+mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList
-- mod-button1 %! Set the window to floating mode and move by dragging
- [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w
- >> windows W.shiftMaster))
+ [ ((modMask, button1), \w -> focus w >> mouseMoveWindow w
+ >> windows W.shiftMaster)
-- mod-button2 %! Raise the window to the top of the stack
- , ((modMask, button2), (\w -> focus w >> windows W.shiftMaster))
+ , ((modMask, button2), \w -> focus w >> windows W.shiftMaster)
-- mod-button3 %! Set the window to floating mode and resize by dragging
- , ((modMask, button3), (\w -> focus w >> mouseResizeWindow w
- >> windows W.shiftMaster))
+ , ((modMask, button3), \w -> focus w >> mouseResizeWindow w
+ >> windows W.shiftMaster)
-- you may also bind events to the mouse scroll wheel (button4 and button5)
]
@@ -248,4 +248,4 @@ defaultConfig = XConfig
, XMonad.manageHook = manageHook
, XMonad.handleEventHook = handleEventHook
, XMonad.focusFollowsMouse = focusFollowsMouse
- } \ No newline at end of file
+ }
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index abe5485..8acada8 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -456,7 +456,7 @@ recompile force = io $ do
then do
-- temporarily disable SIGCHLD ignoring:
uninstallSignalHandlers
- status <- bracket (openFile err WriteMode) hClose $ \h -> do
+ status <- bracket (openFile err WriteMode) hClose $ \h ->
waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-ilib", "-fforce-recomp", "-v0", "-o",binn] (Just dir)
Nothing Nothing Nothing (Just h)
diff --git a/XMonad/Layout.hs b/XMonad/Layout.hs
index 96947f5..faa2246 100644
--- a/XMonad/Layout.hs
+++ b/XMonad/Layout.hs
@@ -125,7 +125,7 @@ instance LayoutClass l a => LayoutClass (Mirror l) a where
-- | Mirror a rectangle.
mirrorRect :: Rectangle -> Rectangle
-mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
+mirrorRect (Rectangle rx ry rw rh) = Rectangle ry rx rh rw
------------------------------------------------------------------------
-- LayoutClass selection manager
@@ -173,7 +173,7 @@ choose (Choose d l r) d' ml mr = f lr
instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
runLayout (W.Workspace i (Choose L l r) ms) =
- fmap (second . fmap $ flip (Choose L) $ r) . runLayout (W.Workspace i l ms)
+ fmap (second . fmap $ flip (Choose L) r) . runLayout (W.Workspace i l ms)
runLayout (W.Workspace i (Choose R l r) ms) =
fmap (second . fmap $ Choose R l) . runLayout (W.Workspace i r ms)
@@ -194,7 +194,7 @@ instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
R -> choose c R Nothing =<< handle r NextNoWrap
- handleMessage c@(Choose _ l _) m | Just FirstLayout <- fromMessage m = do
+ handleMessage c@(Choose _ l _) m | Just FirstLayout <- fromMessage m =
flip (choose c L) Nothing =<< handle l FirstLayout
handleMessage c@(Choose d l r) m | Just ReleaseResources <- fromMessage m =
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index d784951..f0391bc 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -210,7 +210,7 @@ clientMask = structureNotifyMask .|. enterWindowMask .|. propertyChangeMask
setInitialProperties :: Window -> X ()
setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
setWMState w iconicState
- io $ selectInput d w $ clientMask
+ io $ selectInput d w clientMask
bw <- asks (borderWidth . config)
io $ setWindowBorderWidth d w bw
-- we must initially set the color of new windows, to maintain invariants
@@ -320,14 +320,13 @@ setFocusX w = withWindowSet $ \ws -> do
dpy <- asks display
-- clear mouse button grab and border on other windows
- forM_ (W.current ws : W.visible ws) $ \wk -> do
- forM_ (W.index (W.view (W.tag (W.workspace wk)) ws)) $ \otherw -> do
+ forM_ (W.current ws : W.visible ws) $ \wk ->
+ forM_ (W.index (W.view (W.tag (W.workspace wk)) ws)) $ \otherw ->
setButtonGrab True otherw
-- If we ungrab buttons on the root window, we lose our mouse bindings.
whenX (not <$> isRoot w) $ setButtonGrab False w
- io $ do setInputFocus dpy w revertToPointerRoot 0
- -- raiseWindow dpy w
+ io $ setInputFocus dpy w revertToPointerRoot 0
------------------------------------------------------------------------
-- Message handling
@@ -338,7 +337,7 @@ sendMessage :: Message a => a -> X ()
sendMessage a = do
w <- W.workspace . W.current <$> gets windowset
ml' <- handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing
- whenJust ml' $ \l' -> do
+ whenJust ml' $ \l' ->
windows $ \ws -> ws { W.current = (W.current ws)
{ W.workspace = (W.workspace $ W.current ws)
{ W.layout = l' }}}
@@ -438,7 +437,7 @@ floatLocation w = withDisplay $ \d -> do
(fi (wa_width wa + bw*2) % fi (rect_width sr))
(fi (wa_height wa + bw*2) % fi (rect_height sr))
- return (W.screen $ sc, rr)
+ return (W.screen sc, rr)
where fi x = fromIntegral x
-- | Given a point, determine the screen (if any) that contains it.
@@ -508,7 +507,7 @@ mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
wa <- io $ getWindowAttributes d w
sh <- io $ getWMNormalHints d w
io $ warpPointer d none w 0 0 0 0 (fromIntegral (wa_width wa)) (fromIntegral (wa_height wa))
- mouseDrag (\ex ey -> do
+ mouseDrag (\ex ey ->
io $ resizeWindow d w `uncurry`
applySizeHintsContents sh (ex - fromIntegral (wa_x wa),
ey - fromIntegral (wa_y wa)))
diff --git a/XMonad/StackSet.hs b/XMonad/StackSet.hs
index 98497cd..72c3edd 100644
--- a/XMonad/StackSet.hs
+++ b/XMonad/StackSet.hs
@@ -52,7 +52,7 @@ module XMonad.StackSet (
) where
import Prelude hiding (filter)
-import Data.Maybe (listToMaybe,isJust)
+import Data.Maybe (listToMaybe,isJust,fromMaybe)
import qualified Data.List as L (deleteBy,find,splitAt,filter,nub)
import Data.List ( (\\) )
import qualified Data.Map as M (Map,insert,delete,empty)
@@ -369,7 +369,7 @@ reverseStack (Stack t ls rs) = Stack t rs ls
--
focusWindow :: (Eq s, Eq a, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
focusWindow w s | Just w == peek s = s
- | otherwise = maybe s id $ do
+ | otherwise = fromMaybe s $ do
n <- findTag w s
return $ until ((Just w ==) . peek) focusUp (view n s)