diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs
index 8a43cd22..639876bf 100644
--- a/XMonad/Actions/GroupNavigation.hs
+++ b/XMonad/Actions/GroupNavigation.hs
@@ -20,7 +20,7 @@
 --
 ----------------------------------------------------------------------
 
-module XMonad.Actions.GroupNavigation ( -- * Usage  
+module XMonad.Actions.GroupNavigation ( -- * Usage
                                         -- $usage
                                         Direction (..)
                                       , nextMatch
@@ -110,13 +110,13 @@ nextMatch dir qry = nextMatchOrDo dir qry (return ())
 -- | Focuses the next window that matches the given boolean query.  If
 -- there is no such window, perform the given action instead.
 nextMatchOrDo :: Direction -> Query Bool -> X () -> X ()
-nextMatchOrDo dir qry act = orderedWindowList dir 
+nextMatchOrDo dir qry act = orderedWindowList dir
                             >>= focusNextMatchOrDo qry act
 
 -- Produces the action to perform depending on whether there's a
 -- matching window
 focusNextMatchOrDo :: Query Bool -> X () -> Seq Window -> X ()
-focusNextMatchOrDo qry act = findM (runQuery qry) 
+focusNextMatchOrDo qry act = findM (runQuery qry)
                              >=> maybe act (windows . SS.focusWindow)
 
 -- Returns the list of windows ordered by workspace as specified in
@@ -126,7 +126,7 @@ orderedWindowList History = liftM (\(HistoryDB w ws) -> maybe ws (ws |>) w) XS.g
 orderedWindowList dir     = withWindowSet $ \ss -> do
   wsids <- asks (Seq.fromList . workspaces . config)
   let wspcs = orderedWorkspaceList ss wsids
-      wins  = dirfun dir 
+      wins  = dirfun dir
               $ Fold.foldl' (><) Seq.empty
               $ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs
       cur   = SS.peek ss
@@ -148,7 +148,7 @@ orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
 --- History navigation, requires a layout modifier -------------------
 
 -- The state extension that holds the history information
-data HistoryDB = HistoryDB (Maybe Window) -- currently focused window 
+data HistoryDB = HistoryDB (Maybe Window) -- currently focused window
                            (Seq Window)   -- previously focused windows
                deriving (Read, Show, Typeable)
 
@@ -182,12 +182,12 @@ flt :: (a -> Bool) -> Seq a -> Seq a
 flt p = Fold.foldl (\xs x -> if p x then xs |> x else xs) Seq.empty
 
 brkl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
-brkl p xs = flip Seq.splitAt xs 
-            $ snd 
+brkl p xs = flip Seq.splitAt xs
+            $ snd
             $ Fold.foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs
   where
     l = Seq.length xs
-    
+
 --- Some sequence helpers --------------------------------------------
 
 -- Rotates the sequence by one position
diff --git a/XMonad/Actions/KeyRemap.hs b/XMonad/Actions/KeyRemap.hs
index 22c48fff..1fe953f5 100644
--- a/XMonad/Actions/KeyRemap.hs
+++ b/XMonad/Actions/KeyRemap.hs
@@ -9,7 +9,7 @@
 -- Stability   :  unstable
 -- Portability :  unportable
 --
--- Remap Keybinding on the fly, e.g having Dvorak char, but everything with Control/Shift 
+-- Remap Keybinding on the fly, e.g having Dvorak char, but everything with Control/Shift
 -- is left us Layout
 --
 -----------------------------------------------------------------------------
@@ -42,7 +42,7 @@ instance ExtensionClass KeymapTable where
 -- $usage
 -- Provides the possibility to remap parts of the keymap to generate different keys
 --
--- * E.g You want to type Programmers Dvorak, but your keybindings should be the normal us layout 
+-- * E.g You want to type Programmers Dvorak, but your keybindings should be the normal us layout
 --   after all
 --
 -- First, you must add all possible keybindings for all layout you want to use:
diff --git a/XMonad/Actions/Navigation2D.hs b/XMonad/Actions/Navigation2D.hs
index 835512ca..27d772b0 100644
--- a/XMonad/Actions/Navigation2D.hs
+++ b/XMonad/Actions/Navigation2D.hs
@@ -16,22 +16,22 @@
 
 module XMonad.Actions.Navigation2D ( -- * Usage
                                      -- $usage
-                                     
+
                                      -- * Finer points
                                      -- $finer_points
-                                     
+
                                      -- * Alternative directional navigation modules
                                      -- $alternatives
-                                     
+
                                      -- * Incompatibilities
                                      -- $incompatibilities
-                                     
+
                                      -- * Detailed technical discussion
                                      -- $technical
 
                                      -- * Exported functions and types
                                      -- #Exports#
-                                     
+
                                      withNavigation2DConfig
                                    , Navigation2DConfig(..)
                                    , defaultNavigation2DConfig
@@ -226,7 +226,7 @@ import XMonad.Util.Types
 
 -- | A rectangle paired with an object
 type Rect a = (a, Rectangle)
-                                         
+
 -- | A shorthand for window-rectangle pairs.  Reduces typing.
 type WinRect = Rect Window
 
@@ -251,7 +251,7 @@ runNav (N _ nav) = nav
 type Generality = Int
 
 instance Eq Navigation2D where
-  (N x _) == (N y _) = x == y  
+  (N x _) == (N y _) = x == y
 
 instance Ord Navigation2D where
   (N x _) <= (N y _) = x <= y
@@ -302,7 +302,7 @@ data Navigation2DConfig = Navigation2DConfig
 
 -- | Shorthand for the tedious screen type
 type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-                          
+
 -- So we can store the configuration in extensible state
 instance ExtensionClass Navigation2DConfig where
   initialValue = defaultNavigation2DConfig
@@ -755,7 +755,7 @@ wrapOffsets winset = (max_x - min_x, max_y - min_y)
     max_x = fi $ maximum $ map (\r -> rect_x r + (fi $ rect_width  r)) rects
     max_y = fi $ maximum $ map (\r -> rect_y r + (fi $ rect_height r)) rects
     rects = map snd $ visibleWorkspaces winset False
-    
+
 
 -- | Returns the list of screens sorted primarily by their centers'
 -- x-coordinates and secondarily by their y-coordinates.
diff --git a/XMonad/Actions/Workscreen.hs b/XMonad/Actions/Workscreen.hs
index 80f1b370..365ef4b7 100644
--- a/XMonad/Actions/Workscreen.hs
+++ b/XMonad/Actions/Workscreen.hs
@@ -3,11 +3,11 @@
 -- Module     :  XMonad.Actions.Workscreen
 -- Copyright  :  (c) 2012 kedals0
 -- License    :  BSD3-style (see LICENSE)
--- 
+--
 -- Maintainer :  Dal <kedasl0@gmail.com>
 -- Stability  :  unstable
 -- Portability:  unportable
--- 
+--
 -- A workscreen permits to display a set of workspaces on several
 -- screens. In xinerama mode, when a workscreen is viewed, workspaces
 -- associated to all screens are visible.
@@ -48,7 +48,7 @@ import XMonad.Actions.OnScreen
 -- >                    return ()
 --
 -- Then, replace normal workspace view and shift keybinding:
--- 
+--
 -- > [((m .|. modm, k), f i)
 -- >      | (i, k) <- zip [0..] [1..12]
 -- >      , (f, m) <- [(Workscreen.viewWorkscreen, 0), (Workscreen.shiftToWorkscreen, shiftMask)]]
@@ -67,7 +67,7 @@ instance ExtensionClass WorkscreenStorage where
 -- | Helper to group workspaces. Multiply workspace by screens number.
 expandWorkspace :: Int -> [WorkspaceId] -> [WorkspaceId]
 expandWorkspace nscr ws = concat $ map expandId ws
-  where expandId wsId = let t = wsId ++ "_" 
+  where expandId wsId = let t = wsId ++ "_"
                         in map ((++) t . show ) [1..nscr]
 
 -- | Create workscreen list from workspace list. Group workspaces to
@@ -95,7 +95,7 @@ viewWorkscreen wscrId = do (WorkscreenStorage c a) <- XS.get
                            XS.put newWorkscreenStorage
 
 viewWorkscreen' :: Workscreen -> WindowSet -> WindowSet
-viewWorkscreen' (Workscreen _ ws) = \s -> foldl wsToSc' s (zip [0..] ws) 
+viewWorkscreen' (Workscreen _ ws) = \s -> foldl wsToSc' s (zip [0..] ws)
   where wsToSc' s (scr,wsId) = greedyViewOnScreen scr wsId s
 
 shiftWs :: [WorkspaceId] -> [WorkspaceId]
diff --git a/XMonad/Hooks/DebugKeyEvents.hs b/XMonad/Hooks/DebugKeyEvents.hs
index af8184ca..b0e44874 100644
--- a/XMonad/Hooks/DebugKeyEvents.hs
+++ b/XMonad/Hooks/DebugKeyEvents.hs
@@ -45,7 +45,7 @@ import           System.IO                       (hPutStrLn
 -- Logged key events look like:
 --
 -- @keycode 53 sym 120 (0x78, "x") mask 0x0 () clean 0x0 ()@
--- 
+--
 -- The @mask@ and @clean@ indicate the modifiers pressed along with
 -- the key; @mask@ is raw, and @clean@ is what @xmonad@ sees after
 -- sanitizing it (removing @numberLockMask@, etc.)
diff --git a/XMonad/Hooks/FadeWindows.hs b/XMonad/Hooks/FadeWindows.hs
index 9e72e028..30e1de41 100644
--- a/XMonad/Hooks/FadeWindows.hs
+++ b/XMonad/Hooks/FadeWindows.hs
@@ -105,7 +105,7 @@ import           Graphics.X11.Xlib.Extras                (Event(..))
 --
 -- "XMonad.Doc.Extending#Editing_the_event_hook"
 -- (which sadly doesnt exist at the time of writing...)
--- 
+--
 -- /WARNING:/  This module is very good at triggering bugs in
 -- compositing managers.  Symptoms range from windows not being
 -- repainted until the compositing manager is restarted or the
diff --git a/XMonad/Hooks/ICCCMFocus.hs b/XMonad/Hooks/ICCCMFocus.hs
index 0761b9f8..ae55d6a6 100644
--- a/XMonad/Hooks/ICCCMFocus.hs
+++ b/XMonad/Hooks/ICCCMFocus.hs
@@ -20,7 +20,7 @@
 module XMonad.Hooks.ICCCMFocus
 {-# DEPRECATED "XMonad.Hooks.ICCCMFocus: xmonad>0.10 core merged issue 177" #-}
 (
-  atom_WM_TAKE_FOCUS  
+  atom_WM_TAKE_FOCUS
 , takeFocusX
 , takeTopFocus
 ) where
@@ -38,5 +38,5 @@ takeFocusX _w = return ()
 takeTopFocus ::
   X ()
 takeTopFocus =
-  (withWindowSet $ maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D"  
+  (withWindowSet $ maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D"
 
diff --git a/XMonad/Hooks/UrgencyHook.hs b/XMonad/Hooks/UrgencyHook.hs
index c4c7f8ec..82c20fe1 100644
--- a/XMonad/Hooks/UrgencyHook.hs
+++ b/XMonad/Hooks/UrgencyHook.hs
@@ -438,8 +438,8 @@ instance UrgencyHook FocusHook where
 --
 --   > withUrgencyHookC BorderUrgencyHook { urgencyBorderColor = "#ff0000" } urgencyConfig { suppressWhen = Never } ...
 --
---   (This should be @urgentBorderColor@ but that breaks "XMonad.Layout.Decoration".  
---   @borderColor@ breaks anyone using 'XPConfig' from "XMonad.Prompt".  We need to 
+--   (This should be @urgentBorderColor@ but that breaks "XMonad.Layout.Decoration".
+--   @borderColor@ breaks anyone using 'XPConfig' from "XMonad.Prompt".  We need to
 --   think a bit more about namespacing issues, maybe.)
 
 borderUrgencyHook :: String -> Window -> X ()
diff --git a/XMonad/Layout/Groups.hs b/XMonad/Layout/Groups.hs
index e1236ab5..e5ea9773 100644
--- a/XMonad/Layout/Groups.hs
+++ b/XMonad/Layout/Groups.hs
@@ -70,9 +70,9 @@ import Control.Monad (forM)
 -- group, and the layout with which the groups themselves will
 -- be arranged on the screen.
 --
--- The "XMonad.Layout.Groups.Examples" and "XMonad.Layout.Groups.Wmii" 
--- modules contain examples of layouts that can be defined with this 
--- combinator. They're also the recommended starting point 
+-- The "XMonad.Layout.Groups.Examples" and "XMonad.Layout.Groups.Wmii"
+-- modules contain examples of layouts that can be defined with this
+-- combinator. They're also the recommended starting point
 -- if you are a beginner and looking for something you can use easily.
 --
 -- One thing to note is that 'Groups'-based layout have their own
@@ -81,7 +81,7 @@ import Control.Monad (forM)
 -- will have no visible effect, and those like 'XMonad.StackSet.focusUp'
 -- will focus the windows in an unpredictable order. For a better way of
 -- rearranging windows and moving focus in such a layout, see the
--- example 'ModifySpec's (to be passed to the 'Modify' message) provided 
+-- example 'ModifySpec's (to be passed to the 'Modify' message) provided
 -- by this module.
 --
 -- If you use both 'Groups'-based and other layouts, The "XMonad.Layout.Groups.Helpers"
@@ -105,7 +105,7 @@ group l l2 = Groups l l2 startingGroups (U 1 0)
 data Uniq = U Integer Integer
   deriving (Eq, Show, Read)
 
--- | From a seed, generate an infinite list of keys and a new 
+-- | From a seed, generate an infinite list of keys and a new
 -- seed. All keys generated with this method will be different
 -- provided you don't use 'gen' again with a key from the list.
 -- (if you need to do that, see 'split' instead)
@@ -121,7 +121,7 @@ gen (U i1 i2) = (U (i1+1) i2, zipWith U (repeat i1) [i2..])
 
 -- | Add a unique identity to a layout so we can
 -- follow it around.
-data WithID l a = ID { getID :: Uniq 
+data WithID l a = ID { getID :: Uniq
                      , unID :: (l a)}
   deriving (Show, Read)
 
@@ -133,15 +133,15 @@ instance Eq (WithID l a) where
     ID id1 _ == ID id2 _ = id1 == id2
 
 instance LayoutClass l a => LayoutClass (WithID l) a where
-    runLayout ws@W.Workspace { W.layout = ID id l } r 
-        = do (placements, ml') <- flip runLayout r 
+    runLayout ws@W.Workspace { W.layout = ID id l } r
+        = do (placements, ml') <- flip runLayout r
                                      ws { W.layout = l}
              return (placements, ID id <$> ml')
     handleMessage (ID id l) sm = do ml' <- handleMessage l sm
                                     return $ ID id <$> ml'
     description (ID _ l) = description l
 
-          
+
 
 -- * The 'Groups' layout
 
@@ -211,7 +211,7 @@ modifyGroups f g = let (seed', id:_) = gen (seed g)
 
 -- | Adapt our groups to a new stack.
 -- This algorithm handles window additions and deletions correctly,
--- ignores changes in window ordering, and tries to react to any 
+-- ignores changes in window ordering, and tries to react to any
 -- other stack changes as gracefully as possible.
 readapt :: Eq a => Zipper a -> Groups l l2 a -> Groups l l2 a
 readapt z g = let mf = getFocusZ z
@@ -233,7 +233,7 @@ removeDeleted :: Eq a => Zipper a -> Zipper a -> Zipper a
 removeDeleted z = filterZ_ (flip elemZ z)
 
 -- | Identify the windows not already in a group.
-findNewWindows :: Eq a => [a] -> Zipper (Group l a) 
+findNewWindows :: Eq a => [a] -> Zipper (Group l a)
                -> (Zipper (Group l a), [a])
 findNewWindows as gs = (gs, foldrZ_ removePresent as gs)
     where removePresent g as' = filter (not . flip elemZ (gZipper g)) as'
@@ -279,10 +279,10 @@ instance (LayoutClass l Window, LayoutClass l2 (Group l Window))
 
                let placements = concatMap fst results
                    newL = justMakeNew l mpart' (map snd results ++ hidden')
-                                        
+
                return $ (placements, newL)
 
-        handleMessage l@(Groups _ p _ _) sm | Just (ToEnclosing sm') <- fromMessage sm 
+        handleMessage l@(Groups _ p _ _) sm | Just (ToEnclosing sm') <- fromMessage sm
             = do mp' <- handleMessage p sm'
                  return $ maybeMakeNew l mp' []
 
@@ -316,7 +316,7 @@ instance (LayoutClass l Window, LayoutClass l2 (Group l Window))
                             step _ = return Nothing
 
 
-justMakeNew :: Groups l l2 a -> Maybe (l2 (Group l a)) -> [Maybe (WithID l a)] 
+justMakeNew :: Groups l l2 a -> Maybe (l2 (Group l a)) -> [Maybe (WithID l a)]
             -> Maybe (Groups l l2 a)
 justMakeNew g mpart' ml's = Just g { partitioner = fromMaybe (partitioner g) mpart'
                                    , groups = combine (groups g) ml's }
@@ -339,7 +339,7 @@ refocus g = case getFocusZ $ gZipper $ W.focus $ groups g
 
 -- ** ModifySpec type
 
--- | Type of functions describing modifications to a 'Groups' layout. They 
+-- | Type of functions describing modifications to a 'Groups' layout. They
 -- are transformations on 'Zipper's of groups.
 --
 -- Things you shouldn't do:
@@ -358,7 +358,7 @@ refocus g = case getFocusZ $ gZipper $ W.focus $ groups g
 -- 'ModifySpec's as arguments, or returning them,  you'll need to write a type
 -- signature and add @{-# LANGUAGE Rank2Types #-}@ at the beginning
 type ModifySpec = forall l. WithID l Window
-                -> Zipper (Group l Window) 
+                -> Zipper (Group l Window)
                 -> Zipper (Group l Window)
 
 -- | Apply a ModifySpec.
@@ -367,7 +367,7 @@ applySpec f g = let (seed', id:ids) = gen $ seed g
                     g' = flip modifyGroups g $ f (ID id $ baseLayout g)
                                                >>> toTags
                                                >>> foldr reID ((ids, []), [])
-                                               >>> snd 
+                                               >>> snd
                                                >>> fromTags
                 in case groups g == groups g' of
                      True -> Nothing
@@ -448,7 +448,7 @@ _removeFocused (W.Stack f [] []) = (f, Nothing)
 
 -- helper
 _moveToNewGroup :: WithID l Window -> W.Stack (Group l Window)
-                -> (Group l Window -> Zipper (Group l Window) 
+                -> (Group l Window -> Zipper (Group l Window)
                                    -> Zipper (Group l Window))
                 -> Zipper (Group l Window)
 _moveToNewGroup l0 s insertX | G l (Just f) <- W.focus s
@@ -456,7 +456,7 @@ _moveToNewGroup l0 s insertX | G l (Just f) <- W.focus s
           s' = s { W.focus = G l f' }
       in insertX (G l0 $ singletonZ w) $ Just s'
 _moveToNewGroup _ s _ = Just s
- 
+
 -- | Move the focused window to a new group before the current one.
 moveToNewGroupUp :: ModifySpec
 moveToNewGroupUp _ Nothing = Nothing
diff --git a/XMonad/Layout/Groups/Examples.hs b/XMonad/Layout/Groups/Examples.hs
index a5d17706..9407c9b9 100644
--- a/XMonad/Layout/Groups/Examples.hs
+++ b/XMonad/Layout/Groups/Examples.hs
@@ -67,12 +67,12 @@ import XMonad.Layout.Simplest
 
 
 -- $usage
--- This module contains example 'G.Groups'-based layouts. 
+-- This module contains example 'G.Groups'-based layouts.
 -- You can either import this module directly, or look at its source
 -- for ideas of how "XMonad.Layout.Groups" may be used.
 --
 -- You can use the contents of this module by adding
--- 
+--
 -- > import XMonad.Layout.Groups.Examples
 --
 -- to the top of your @.\/.xmonad\/xmonad.hs@.
@@ -80,10 +80,10 @@ import XMonad.Layout.Simplest
 -- For more information on using any of the layouts, jump directly
 --   to its \"Example\" section.
 --
--- Whichever layout you choose to use, you will probably want to be 
+-- Whichever layout you choose to use, you will probably want to be
 --   able to move focus and windows between groups in a consistent
 --   manner. For this, you should take a look at the functions from
---   the "XMonad.Layout.Groups.Helpers" module, which are all 
+--   the "XMonad.Layout.Groups.Helpers" module, which are all
 --   re-exported by this module.
 --
 -- For more information on how to extend your layour hook and key bindings, see
@@ -99,7 +99,7 @@ data GroupEQ a = GroupEQ
 instance Eq a => EQF GroupEQ (G.Group l a) where
     eq _ (G.G l1 _) (G.G l2 _) = G.sameID l1 l2
 
-zoomRowG :: (Eq a, Show a, Read a, Show (l a), Read (l a)) 
+zoomRowG :: (Eq a, Show a, Read a, Show (l a), Read (l a))
             => ZoomRow GroupEQ (G.Group l a)
 zoomRowG = zoomRowWith GroupEQ
 
@@ -171,10 +171,10 @@ toggleWindowFull = sendMessage ZoomFullToggle
 
 -- $example2
 -- A layout which arranges windows into tabbed groups, and the groups
--- themselves according to XMonad's default algorithm 
+-- themselves according to XMonad's default algorithm
 -- (@'Tall' ||| 'Mirror' 'Tall' ||| 'Full'@). As their names
--- indicate, 'tallTabs' starts as 'Tall', 'mirrorTallTabs' starts 
--- as 'Mirror' 'Tall' and 'fullTabs' starts as 'Full', but in any 
+-- indicate, 'tallTabs' starts as 'Tall', 'mirrorTallTabs' starts
+-- as 'Mirror' 'Tall' and 'fullTabs' starts as 'Full', but in any
 -- case you can freely switch between the three afterwards.
 --
 -- You can use any of these three layouts by including it in your layout hook.
@@ -204,7 +204,7 @@ data TiledTabsConfig s = TTC { vNMaster :: Int
 defaultTiledTabsConfig :: TiledTabsConfig DefaultShrinker
 defaultTiledTabsConfig = TTC 1 0.5 (3/100) 1 0.5 (3/100) shrinkText defaultTheme
 
-fullTabs c = _tab c $ G.group _tabs $ Full ||| _vert c ||| _horiz c 
+fullTabs c = _tab c $ G.group _tabs $ Full ||| _vert c ||| _horiz c
 
 tallTabs c = _tab c $ G.group _tabs $ _vert c ||| _horiz c ||| Full
 
diff --git a/XMonad/Layout/Groups/Helpers.hs b/XMonad/Layout/Groups/Helpers.hs
index 972f3570..268ab721 100644
--- a/XMonad/Layout/Groups/Helpers.hs
+++ b/XMonad/Layout/Groups/Helpers.hs
@@ -69,7 +69,7 @@ import qualified Data.Map as M
 -- This module provides actions that try to send 'G.GroupsMessage's, and
 -- fall back to the classic way if the current layout doesn't hande them.
 -- They are in the section called \"Layout-generic actions\".
--- 
+--
 -- The sections \"Groups-specific actions\" contains actions that don't make
 -- sense for non-'G.Groups'-based layouts. These are simply wrappers around
 -- the equivalent 'G.GroupsMessage's, but are included so you don't have to
@@ -139,7 +139,7 @@ ifFloat x1 x2 = withFocused $ \w -> do floats <- getFloats
 
 focusNonFloat :: X ()
 focusNonFloat = alt2 G.Refocus helper
-    where helper = withFocused $ \w -> do 
+    where helper = withFocused $ \w -> do
                      ws <- getWindows
                      floats <- getFloats
                      let (before,  after) = span (/=w) ws
@@ -170,7 +170,7 @@ focusNonFloatDown = alt2 (G.Modify G.focusDown) $ focusHelper not id
 
 focusFloatUp :: X ()
 focusFloatUp = focusHelper id reverse
-                 
+
 focusFloatDown :: X ()
 focusFloatDown = focusHelper id id
 
diff --git a/XMonad/Layout/Groups/Wmii.hs b/XMonad/Layout/Groups/Wmii.hs
index 92297fec..da45149b 100644
--- a/XMonad/Layout/Groups/Wmii.hs
+++ b/XMonad/Layout/Groups/Wmii.hs
@@ -17,7 +17,7 @@
 
 module XMonad.Layout.Groups.Wmii ( -- * Usage
                                    -- $usage
-                                   
+
                                    wmii
                                  , zoomGroupIn
                                  , zoomGroupOut
@@ -48,9 +48,9 @@ import XMonad.Layout.Simplest
 
 
 -- $usage
--- This module provides a layout inspired by the one used by the wmii 
+-- This module provides a layout inspired by the one used by the wmii
 -- (<http://wmii.suckless.org>) window manager.
--- Windows are arranged into groups in a horizontal row, and each group can lay out 
+-- Windows are arranged into groups in a horizontal row, and each group can lay out
 -- its windows
 --
 --   * by maximizing the focused one
@@ -59,16 +59,16 @@ import XMonad.Layout.Simplest
 --
 --   * by arranging them in a column.
 --
--- As the groups are arranged in a 'ZoomRow', the relative width of each group can be 
--- increased or decreased at will. Groups can also be set to use the whole screen 
+-- As the groups are arranged in a 'ZoomRow', the relative width of each group can be
+-- increased or decreased at will. Groups can also be set to use the whole screen
 -- whenever they have focus.
 --
 -- You can use the contents of this module by adding
--- 
+--
 -- > import XMonad.Layout.Groups.Wmii
 --
--- to the top of your @.\/.xmonad\/xmonad.hs@, and adding 'wmii' 
--- (with a 'Shrinker' and decoration 'Theme' as 
+-- to the top of your @.\/.xmonad\/xmonad.hs@, and adding 'wmii'
+-- (with a 'Shrinker' and decoration 'Theme' as
 -- parameters) to your layout hook, for example:
 --
 -- > myLayout = wmii shrinkText defaultTheme
@@ -92,10 +92,10 @@ import XMonad.Layout.Simplest
 wmii s t = G.group innerLayout zoomRowG
     where column = named "Column" $ Tall 0 (3/100) (1/2)
           tabs = named "Tabs" $ Simplest
-          innerLayout = renamed [CutWordsLeft 3] 
+          innerLayout = renamed [CutWordsLeft 3]
                         $ addTabs s t
-                        $ ignore NextLayout 
-                        $ ignore (JumpToLayout "") $ unEscape 
+                        $ ignore NextLayout
+                        $ ignore (JumpToLayout "") $ unEscape
                            $ column ||| tabs ||| Full
 
 -- | Increase the width of the focused group
diff --git a/XMonad/Layout/ImageButtonDecoration.hs b/XMonad/Layout/ImageButtonDecoration.hs
index cab72fdc..0a44fe72 100644
--- a/XMonad/Layout/ImageButtonDecoration.hs
+++ b/XMonad/Layout/ImageButtonDecoration.hs
@@ -140,7 +140,7 @@ closeButton' = [[1,1,0,0,0,0,0,0,1,1],
 
 
 closeButton :: [[Bool]]
-closeButton = convertToBool closeButton'    
+closeButton = convertToBool closeButton'
 
 -- | A function intended to be plugged into the 'decorationCatchClicksHook' of a decoration.
 -- It will intercept clicks on the buttons of the decoration and invoke the associated action.
diff --git a/XMonad/Layout/LayoutBuilderP.hs b/XMonad/Layout/LayoutBuilderP.hs
index aee6c6a4..b76f3d9e 100644
--- a/XMonad/Layout/LayoutBuilderP.hs
+++ b/XMonad/Layout/LayoutBuilderP.hs
@@ -40,7 +40,7 @@ import qualified XMonad.Layout.LayoutBuilder as B
 --
 -- compare "XMonad.Util.Invisible"
 
--- | Type class for predicates. This enables us to manage not only Windows, 
+-- | Type class for predicates. This enables us to manage not only Windows,
 -- but any objects, for which instance Predicate is defined.
 --
 -- Another instance exists in XMonad.Util.WindowPropertiesRE in xmonad-extras
diff --git a/XMonad/Layout/Renamed.hs b/XMonad/Layout/Renamed.hs
index 5d55b862..002a7254 100644
--- a/XMonad/Layout/Renamed.hs
+++ b/XMonad/Layout/Renamed.hs
@@ -24,7 +24,7 @@ import XMonad
 import XMonad.Layout.LayoutModifier
 
 -- $usage
--- You can use this module by adding 
+-- You can use this module by adding
 --
 -- > import XMonad.Layout.Renamed
 --
diff --git a/XMonad/Layout/ZoomRow.hs b/XMonad/Layout/ZoomRow.hs
index c279bbaf..6f86726c 100644
--- a/XMonad/Layout/ZoomRow.hs
+++ b/XMonad/Layout/ZoomRow.hs
@@ -42,7 +42,7 @@ import XMonad.Layout.Decoration (fi)
 
 import Data.Maybe (fromMaybe)
 import Control.Arrow (second)
- 
+
 -- $usage
 -- This module provides a layout which places all windows in a single
 -- row; the size occupied by each individual window can be increased
@@ -80,9 +80,9 @@ zoomRow :: (Eq a, Show a, Read a) => ZoomRow ClassEQ a
 zoomRow = ZC ClassEQ emptyZ
 
 -- $noneq
--- Haskell's 'Eq' class is usually concerned with structural equality, whereas 
+-- Haskell's 'Eq' class is usually concerned with structural equality, whereas
 -- what this layout really wants is for its elements to have a unique identity,
--- even across changes. There are cases (such as, importantly, 'Window's) where 
+-- even across changes. There are cases (such as, importantly, 'Window's) where
 -- the 'Eq' instance for a type actually does that, but if you want to lay
 -- out something more exotic than windows and your 'Eq' means something else,
 -- you can use the following.
@@ -92,7 +92,7 @@ zoomRow = ZC ClassEQ emptyZ
 -- sure that the layout never has to handle two \"equal\" elements
 -- at the same time (it won't do any huge damage, but might behave
 -- a bit strangely).
-zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a) 
+zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a)
                => f a -> ZoomRow f a
 zoomRowWith f = ZC f emptyZ
 
@@ -185,7 +185,7 @@ zoomReset = ZoomTo 1
 
 -- * LayoutClass instance
 
-instance (EQF f a, Show a, Read a, Show (f a), Read (f a)) 
+instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
     => LayoutClass (ZoomRow f) a where
     description (ZC _ Nothing) = "ZoomRow"
     description (ZC _ (Just s)) = "ZoomRow" ++ if full $ W.focus s
@@ -197,7 +197,7 @@ instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
 
     doLayout (ZC f zelts) r@(Rectangle _ _ w _) s
         = let elts = W.integrate' zelts
-              zelts' = mapZ_ (\a -> fromMaybe (E a 1 False) 
+              zelts' = mapZ_ (\a -> fromMaybe (E a 1 False)
                                     $ lookupBy (eq f) a elts) $ Just s
               elts' = W.integrate' zelts'
 
@@ -251,7 +251,7 @@ instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
         = case fromMessage sm of
             Just (Zoom r') -> Just $ ZC f $ setFocus zelts $ E a (r*r') b
             Just (ZoomTo r') -> Just $ ZC f $ setFocus zelts $ E a r' b
-            Just ZoomFullToggle -> pureMessage (ZC f zelts) 
+            Just ZoomFullToggle -> pureMessage (ZC f zelts)
                                      $ SomeMessage $ ZoomFull $ not b
             _ -> Nothing
 
diff --git a/XMonad/Util/Image.hs b/XMonad/Util/Image.hs
index ff0ecdc8..554ba585 100644
--- a/XMonad/Util/Image.hs
+++ b/XMonad/Util/Image.hs
@@ -29,7 +29,7 @@ data Placement = OffsetLeft Int Int   -- ^ An exact amount of pixels from the up
                  | CenterLeft Int        -- ^ Centered in the y-axis, an amount of pixels from the left
                  | CenterRight Int       -- ^ Centered in the y-axis, an amount of pixels from the right
                    deriving (Show, Read)
-                   
+
 -- $usage
 -- This module uses matrices of boolean values as images. When drawing them,
 -- a True value tells that we want the fore color, and a False value that we
diff --git a/XMonad/Util/Stack.hs b/XMonad/Util/Stack.hs
index eb58a16f..9455d71e 100644
--- a/XMonad/Util/Stack.hs
+++ b/XMonad/Util/Stack.hs
@@ -145,7 +145,7 @@ swapUpZ (Just s) = Just s { W.up = reverse (W.down s), W.down = [] }
 swapDownZ :: Zipper a -> Zipper a
 swapDownZ Nothing = Nothing
 swapDownZ (Just s) | d:down <- W.down s = Just s { W.down = down, W.up = d:W.up s }
-swapDownZ (Just s) = Just s { W.up = [], W.down = reverse (W.up s) } 
+swapDownZ (Just s) = Just s { W.up = [], W.down = reverse (W.up s) }
 
 -- | Swap the focused element with the first one
 swapMasterZ :: Zipper a -> Zipper a
@@ -197,7 +197,7 @@ sortByZ f = fromTags . sortBy (adapt f) . toTags
     where adapt g e1 e2 = g (fromE e1) (fromE e2)
 
 -- ** Maps
-             
+
 -- | Map a function over a stack. The boolean argument indcates whether
 -- the current element is the focused one
 mapZ :: (Bool -> a -> b) -> Zipper a -> Zipper b
diff --git a/XMonad/Util/XSelection.hs b/XMonad/Util/XSelection.hs
index 330f2e87..5ab06de9 100644
--- a/XMonad/Util/XSelection.hs
+++ b/XMonad/Util/XSelection.hs
@@ -82,7 +82,7 @@ promptSelection = unsafePromptSelection
 safePromptSelection app = join $ io $ liftM (safeSpawn app . return) getSelection
 unsafePromptSelection app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " " ++ x) getSelection
 
-{- | A wrapper around 'promptSelection' and its safe variant. They take two parameters, the 
+{- | A wrapper around 'promptSelection' and its safe variant. They take two parameters, the
      first is a function that transforms strings, and the second is the application to run.
      The transformer essentially transforms the selection in X.
      One example is to wrap code, such as a command line action copied out of the browser
diff --git a/XMonad/Util/XUtils.hs b/XMonad/Util/XUtils.hs
index 7df77650..b7e0fec2 100644
--- a/XMonad/Util/XUtils.hs
+++ b/XMonad/Util/XUtils.hs
@@ -38,7 +38,7 @@ import XMonad.Util.Image
 import Control.Monad
 
 -- $usage
--- See "XMonad.Layout.Tabbed" or "XMonad.Layout.DragPane" or 
+-- See "XMonad.Layout.Tabbed" or "XMonad.Layout.DragPane" or
 -- "XMonad.Layout.Decoration" for usage examples
 
 -- | Compute the weighted average the colors of two given Pixel values.
@@ -163,7 +163,7 @@ paintTextAndIcons w fs wh ht bw bc borc ffc fbc als strs i_als icons = do
 -- drawn inside it.
 -- Not exported.
 paintWindow' :: Window -> Rectangle -> Dimension -> String -> String
-                -> Maybe (XMonadFont,String,String,[(String, (Position, Position))]) 
+                -> Maybe (XMonadFont,String,String,[(String, (Position, Position))])
                 -> Maybe (String, String, [((Position, Position), [[Bool]])]) -> X ()
 paintWindow' win (Rectangle _ _ wh ht) bw color b_color strStuff iconStuff = do
   d  <- asks display