diff --git a/XMonad/Actions/Commands.hs b/XMonad/Actions/Commands.hs
index 241fa16b..dd9a6b56 100644
--- a/XMonad/Actions/Commands.hs
+++ b/XMonad/Actions/Commands.hs
@@ -32,7 +32,7 @@ import XMonad.Util.Dmenu (dmenu)
 
 import qualified Data.Map as M
 import System.Exit
-import Data.Maybe
+import XMonad.Prelude
 
 -- $usage
 --
diff --git a/XMonad/Actions/CycleSelectedLayouts.hs b/XMonad/Actions/CycleSelectedLayouts.hs
index 1a2d526e..cea44c29 100644
--- a/XMonad/Actions/CycleSelectedLayouts.hs
+++ b/XMonad/Actions/CycleSelectedLayouts.hs
@@ -18,8 +18,7 @@ module XMonad.Actions.CycleSelectedLayouts (
     cycleThroughLayouts) where
 
 import XMonad
-import Data.List (findIndex)
-import Data.Maybe (fromMaybe)
+import XMonad.Prelude (findIndex, fromMaybe)
 import XMonad.Layout.LayoutCombinators (JumpToLayout(..))
 import qualified XMonad.StackSet as S
 
diff --git a/XMonad/Actions/CycleWS.hs b/XMonad/Actions/CycleWS.hs
index 67895050..4901a4f6 100644
--- a/XMonad/Actions/CycleWS.hs
+++ b/XMonad/Actions/CycleWS.hs
@@ -78,9 +78,7 @@ module XMonad.Actions.CycleWS (
 
                              ) where
 
-import Data.List ( find, findIndex )
-import Data.Maybe ( isNothing, isJust )
-
+import XMonad.Prelude (find, findIndex, isJust, isNothing)
 import XMonad hiding (workspaces)
 import qualified XMonad.Hooks.WorkspaceHistory as WH
 import XMonad.StackSet hiding (filter)
diff --git a/XMonad/Actions/CycleWorkspaceByScreen.hs b/XMonad/Actions/CycleWorkspaceByScreen.hs
index f46e22ba..4fc95013 100644
--- a/XMonad/Actions/CycleWorkspaceByScreen.hs
+++ b/XMonad/Actions/CycleWorkspaceByScreen.hs
@@ -23,14 +23,12 @@ module XMonad.Actions.CycleWorkspaceByScreen (
   , repeatableAction
   ) where
 
-import           Control.Monad
 import           Data.IORef
-import           Data.List
-import           Data.Maybe
 
 import           Graphics.X11.Xlib.Extras
 
 import           XMonad
+import           XMonad.Prelude
 import           XMonad.Hooks.WorkspaceHistory
 import qualified XMonad.StackSet as W
 
diff --git a/XMonad/Actions/DynamicProjects.hs b/XMonad/Actions/DynamicProjects.hs
index 729846da..0833d8b0 100644
--- a/XMonad/Actions/DynamicProjects.hs
+++ b/XMonad/Actions/DynamicProjects.hs
@@ -43,14 +43,10 @@ module XMonad.Actions.DynamicProjects
        ) where
 
 --------------------------------------------------------------------------------
-import Control.Applicative ((<|>))
-import Control.Monad (when, unless)
-import Data.Char (isSpace)
-import Data.List (sort, union, stripPrefix)
 import Data.Map.Strict (Map)
 import qualified Data.Map.Strict as Map
-import Data.Maybe (fromMaybe, isNothing)
 import System.Directory (setCurrentDirectory, getHomeDirectory, makeAbsolute)
+import XMonad.Prelude
 import XMonad
 import XMonad.Actions.DynamicWorkspaces
 import XMonad.Prompt
diff --git a/XMonad/Actions/DynamicWorkspaceGroups.hs b/XMonad/Actions/DynamicWorkspaceGroups.hs
index dc0dc651..e3c7b821 100644
--- a/XMonad/Actions/DynamicWorkspaceGroups.hs
+++ b/XMonad/Actions/DynamicWorkspaceGroups.hs
@@ -36,11 +36,11 @@ module XMonad.Actions.DynamicWorkspaceGroups
     , WSGPrompt
     ) where
 
-import Data.List (find)
 import Control.Arrow ((&&&))
 import qualified Data.Map as M
 
 import XMonad
+import XMonad.Prelude (find)
 import qualified XMonad.StackSet as W
 
 import XMonad.Prompt
diff --git a/XMonad/Actions/DynamicWorkspaceOrder.hs b/XMonad/Actions/DynamicWorkspaceOrder.hs
index f1755cca..72fec230 100644
--- a/XMonad/Actions/DynamicWorkspaceOrder.hs
+++ b/XMonad/Actions/DynamicWorkspaceOrder.hs
@@ -44,7 +44,7 @@ import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..), doTo)
 
 import qualified Data.Map as M
 import qualified Data.Set as S
-import Data.Maybe (fromJust, fromMaybe)
+import XMonad.Prelude (fromJust, fromMaybe)
 import Data.Ord (comparing)
 
 -- $usage
diff --git a/XMonad/Actions/DynamicWorkspaces.hs b/XMonad/Actions/DynamicWorkspaces.hs
index 2918ef81..2ddcf9a7 100644
--- a/XMonad/Actions/DynamicWorkspaces.hs
+++ b/XMonad/Actions/DynamicWorkspaces.hs
@@ -35,14 +35,12 @@ module XMonad.Actions.DynamicWorkspaces (
                                          WorkspaceIndex
                                        ) where
 
+import XMonad.Prelude (find, isNothing, when)
 import XMonad hiding (workspaces)
 import XMonad.StackSet hiding (filter, modify, delete)
 import XMonad.Prompt.Workspace ( Wor(Wor), workspacePrompt )
 import XMonad.Prompt ( XPConfig, mkXPrompt )
 import XMonad.Util.WorkspaceCompare ( getSortByIndex )
-import Data.List (find)
-import Data.Maybe (isNothing)
-import Control.Monad (when)
 import qualified Data.Map.Strict as Map
 import qualified XMonad.Util.ExtensibleState as XS
 
diff --git a/XMonad/Actions/EasyMotion.hs b/XMonad/Actions/EasyMotion.hs
index f571ca5e..78b1f05b 100644
--- a/XMonad/Actions/EasyMotion.hs
+++ b/XMonad/Actions/EasyMotion.hs
@@ -38,18 +38,13 @@ module XMonad.Actions.EasyMotion ( -- * Usage
                                  ) where
 
 import           XMonad
-import           XMonad.StackSet          as W
+import           XMonad.Prelude
+import qualified XMonad.StackSet          as W
 import           XMonad.Util.Font         (releaseXMF, initXMF, Align(AlignCenter), XMonadFont(..), textExtentsXMF)
-import           XMonad.Util.XUtils       (fi, createNewWindow, paintAndWrite, deleteWindow, showWindow)
-import           Control.Monad            (replicateM)
+import           XMonad.Util.XUtils       (createNewWindow, paintAndWrite, deleteWindow, showWindow)
+
 import           Control.Arrow            ((&&&))
-import           Data.Functor             (($>))
-import           Data.Maybe               (isJust, listToMaybe)
-import qualified Data.Map.Strict as M     (Map, map, mapWithKey, elems)
-import           Data.Set                 (toList)
-import           Graphics.X11.Xlib.Extras (getWindowAttributes, getEvent)
-import qualified Data.List as L           (filter, partition, find, nub)
-import           Data.List                (sortOn)
+import qualified Data.Map.Strict as M     (Map, elems, map, mapWithKey)
 
 -- $usage
 --
@@ -275,9 +270,9 @@ handleSelectWindow c = do
         $ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m
      where
       screenById :: ScreenId -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail)
-      screenById sid = L.find ((== sid) . screen) (W.screens ws)
+      screenById sid = find ((== sid) . W.screen) (W.screens ws)
       visibleWindowsOnScreen :: ScreenId -> [Window]
-      visibleWindowsOnScreen sid = L.filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace
+      visibleWindowsOnScreen sid = filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace
       sortedOverlayWindows :: ScreenId -> X [OverlayWindow]
       sortedOverlayWindows sid = sortOverlayWindows <$> buildOverlayWindows dpy th (visibleWindowsOnScreen sid)
   status <- io $ grabKeyboard dpy rw True grabModeAsync grabModeAsync currentTime
@@ -331,7 +326,7 @@ selectWindow conf =
  where
   -- make sure the key lists don't contain: backspace, our cancel key, or duplicates
   sanitise :: [KeySym] -> [KeySym]
-  sanitise = L.nub . L.filter (`notElem` [xK_BackSpace, cancelKey conf])
+  sanitise = nub . filter (`notElem` [xK_BackSpace, cancelKey conf])
   sanitiseKeys :: ChordKeys -> ChordKeys
   sanitiseKeys cKeys =
     case cKeys of
@@ -381,12 +376,12 @@ handleKeyboard dpy drawFn cancel selected deselected = do
     case x of
       Backspace -> redraw >> handleKeyboard dpy drawFn cancel selected deselected
       _ -> return x
-  isNextOverlayKey keySym = isJust (L.find ((== Just keySym) . listToMaybe .chord) selected)
+  isNextOverlayKey keySym = isJust (find ((== Just keySym) . listToMaybe .chord) selected)
   handleNextOverlayKey keySym =
     case fg of
       [x] -> return $ Selected x
       _   -> handleKeyboard dpy drawFn cancel (trim fg) (clear bg) >>= retryBackspace
    where
-    (fg, bg) = L.partition ((== Just keySym) . listToMaybe . chord) selected
+    (fg, bg) = partition ((== Just keySym) . listToMaybe . chord) selected
     trim = map (\o -> o { chord = tail $ chord o })
     clear = map (\o -> o { chord = [] })
diff --git a/XMonad/Actions/FindEmptyWorkspace.hs b/XMonad/Actions/FindEmptyWorkspace.hs
index 745df464..878bd7ff 100644
--- a/XMonad/Actions/FindEmptyWorkspace.hs
+++ b/XMonad/Actions/FindEmptyWorkspace.hs
@@ -18,9 +18,7 @@ module XMonad.Actions.FindEmptyWorkspace (
     viewEmptyWorkspace, tagToEmptyWorkspace, sendToEmptyWorkspace
   ) where
 
-import Data.List
-import Data.Maybe ( isNothing )
-
+import XMonad.Prelude
 import XMonad
 import XMonad.StackSet
 
diff --git a/XMonad/Actions/FlexibleResize.hs b/XMonad/Actions/FlexibleResize.hs
index be33f141..6be75359 100644
--- a/XMonad/Actions/FlexibleResize.hs
+++ b/XMonad/Actions/FlexibleResize.hs
@@ -20,7 +20,7 @@ module XMonad.Actions.FlexibleResize (
 ) where
 
 import XMonad
-import XMonad.Util.XUtils (fi)
+import XMonad.Prelude (fi)
 import Foreign.C.Types
 
 -- $usage
diff --git a/XMonad/Actions/FloatSnap.hs b/XMonad/Actions/FloatSnap.hs
index 002db4f1..47a66adf 100644
--- a/XMonad/Actions/FloatSnap.hs
+++ b/XMonad/Actions/FloatSnap.hs
@@ -27,8 +27,7 @@ module XMonad.Actions.FloatSnap (
                 ifClick') where
 
 import XMonad
-import Data.List (sort)
-import Data.Maybe (listToMaybe,fromJust,isNothing)
+import XMonad.Prelude (fromJust, isNothing, listToMaybe, sort)
 import qualified XMonad.StackSet as W
 import qualified Data.Set as S
 
diff --git a/XMonad/Actions/GridSelect.hs b/XMonad/Actions/GridSelect.hs
index a0c46b88..436c259d 100644
--- a/XMonad/Actions/GridSelect.hs
+++ b/XMonad/Actions/GridSelect.hs
@@ -78,15 +78,14 @@ module XMonad.Actions.GridSelect (
     -- * Types
     TwoDState,
     ) where
-import Data.Maybe
+import Control.Arrow ((***))
 import Data.Bits
-import Data.Char
 import Data.Ord (comparing)
 import Control.Monad.State
-import Control.Arrow
 import Data.List as L
 import qualified Data.Map as M
 import XMonad hiding (liftX)
+import XMonad.Prelude
 import XMonad.Util.Font
 import XMonad.Prompt (mkUnmanagedWindow)
 import XMonad.StackSet as W
diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs
index 37508a08..d6329527 100644
--- a/XMonad/Actions/GroupNavigation.hs
+++ b/XMonad/Actions/GroupNavigation.hs
@@ -35,15 +35,17 @@ module XMonad.Actions.GroupNavigation ( -- * Usage
 
 import Control.Monad.Reader
 import Control.Monad.State
-import Data.Foldable as Fold
-import Data.Map as Map
-import Data.Sequence as Seq
-import Data.Set as Set
+import Data.Map ((!))
+import qualified Data.Map as Map
+import Data.Sequence (Seq, ViewL (EmptyL, (:<)), viewl, (<|), (><), (|>))
+import qualified Data.Sequence as Seq
+import qualified Data.Set as Set
 import Graphics.X11.Types
 import Prelude hiding (concatMap, drop, elem, filter, null, reverse)
 import XMonad.Core
 import XMonad.ManageHook
 import XMonad.Operations (windows, withFocused)
+import XMonad.Prelude (elem, foldl')
 import qualified XMonad.StackSet as SS
 import qualified XMonad.Util.ExtensibleState as XS
 
@@ -132,7 +134,7 @@ orderedWindowList dir     = withWindowSet $ \ss -> do
   wsids <- asks (Seq.fromList . workspaces . config)
   let wspcs = orderedWorkspaceList ss wsids
       wins  = dirfun dir
-              $ Fold.foldl' (><) Seq.empty
+              $ foldl' (><) Seq.empty
               $ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs
       cur   = SS.peek ss
   return $ maybe wins (rotfun wins) cur
@@ -146,7 +148,7 @@ orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace
 orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
     where
       wspcs      = SS.workspaces ss
-      wspcsMap   = Fold.foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs
+      wspcsMap   = foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs
       wspcs'     = fmap (wspcsMap !) wsids
       isCurWS ws = SS.tag ws == SS.tag (SS.workspace $ SS.current ss)
 
@@ -172,26 +174,11 @@ updateHistory :: HistoryDB -> X HistoryDB
 updateHistory (HistoryDB oldcur oldhist) = withWindowSet $ \ss -> do
   let newcur   = SS.peek ss
       wins     = Set.fromList $ SS.allWindows ss
-      newhist  = flt (`Set.member` wins) (ins oldcur oldhist)
+      newhist  = Seq.filter (`Set.member` wins) (ins oldcur oldhist)
   return $ HistoryDB newcur (del newcur newhist)
   where
     ins x xs = maybe xs (<| xs) x
-    del x xs = maybe xs (\x' -> flt (/= x') xs) x
-
---- Two replacements for Seq.filter and Seq.breakl available only in
---- containers-0.3.0.0, which only ships with ghc 6.12.  Once we
---- decide to no longer support ghc < 6.12, these should be replaced
---- with Seq.filter and Seq.breakl.
-
-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
-            $ 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
+    del x xs = maybe xs (\x' -> Seq.filter (/= x') xs) x
 
 --- Some sequence helpers --------------------------------------------
 
@@ -205,7 +192,7 @@ rotate xs = rotate' (viewl xs)
 -- Rotates the sequence until an element matching the given condition
 -- is at the beginning of the sequence.
 rotateTo :: (a -> Bool) -> Seq a -> Seq a
-rotateTo cond xs = let (lxs, rxs) = brkl cond xs in rxs >< lxs
+rotateTo cond xs = let (lxs, rxs) = Seq.breakl cond xs in rxs >< lxs
 
 --- A monadic find ---------------------------------------------------
 
@@ -239,4 +226,3 @@ isOnAnyVisibleWS = do
       visibleWs = w `elem` allVisible
       unfocused = maybe True (w /=) $ SS.peek ws
   return $ visibleWs && unfocused
-
diff --git a/XMonad/Actions/KeyRemap.hs b/XMonad/Actions/KeyRemap.hs
index 1fe953f5..55b23c92 100644
--- a/XMonad/Actions/KeyRemap.hs
+++ b/XMonad/Actions/KeyRemap.hs
@@ -27,11 +27,10 @@ module XMonad.Actions.KeyRemap (
   ) where
 
 import XMonad
+import XMonad.Prelude
 import XMonad.Util.Paste
-import Data.List
 
 import qualified XMonad.Util.ExtensibleState as XS
-import Control.Monad
 
 
 data KeymapTable = KeymapTable [((KeyMask, KeySym), (KeyMask, KeySym))] deriving (Typeable, Show)
diff --git a/XMonad/Actions/Launcher.hs b/XMonad/Actions/Launcher.hs
index 0857f11e..0c1da173 100644
--- a/XMonad/Actions/Launcher.hs
+++ b/XMonad/Actions/Launcher.hs
@@ -18,10 +18,9 @@ module XMonad.Actions.Launcher(
   , launcherPrompt
 ) where
 
-import           Data.List       (find, findIndex, isPrefixOf, tails)
 import qualified Data.Map        as M
-import           Data.Maybe      (isJust)
 import           XMonad          hiding (config)
+import           XMonad.Prelude
 import           XMonad.Prompt
 import           XMonad.Util.Run
 
diff --git a/XMonad/Actions/MessageFeedback.hs b/XMonad/Actions/MessageFeedback.hs
index d332d43c..b75514d5 100644
--- a/XMonad/Actions/MessageFeedback.hs
+++ b/XMonad/Actions/MessageFeedback.hs
@@ -51,13 +51,11 @@ module XMonad.Actions.MessageFeedback
 
 import XMonad               ( Window )
 import XMonad.Core          ( X(), Message, SomeMessage(..), LayoutClass(..), windowset, catchX, WorkspaceId, Layout, whenJust )
-import XMonad.StackSet      ( Workspace, current, workspace, layout, tag )
 import XMonad.Operations    ( updateLayout, windowBracket, modifyWindowSet )
+import XMonad.Prelude       ( isJust, liftA2, void )
+import XMonad.StackSet      ( Workspace, current, workspace, layout, tag )
 
-import Data.Maybe           ( isJust )
-import Control.Monad        ( void )
 import Control.Monad.State  ( gets )
-import Control.Applicative  ( liftA2 )
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Actions/Minimize.hs b/XMonad/Actions/Minimize.hs
index 73306f6c..4c9c44b1 100644
--- a/XMonad/Actions/Minimize.hs
+++ b/XMonad/Actions/Minimize.hs
@@ -35,6 +35,7 @@ module XMonad.Actions.Minimize
   ) where
 
 import XMonad
+import XMonad.Prelude (fromMaybe, join, listToMaybe)
 import qualified XMonad.StackSet as W
 
 import qualified XMonad.Layout.BoringWindows as BW
@@ -43,8 +44,6 @@ import XMonad.Util.Minimize
 import XMonad.Util.WindowProperties (getProp32)
 
 import Foreign.C.Types (CLong)
-import Control.Monad (join)
-import Data.Maybe (fromMaybe, listToMaybe)
 import qualified Data.List as L
 import qualified Data.Map as M
 
diff --git a/XMonad/Actions/MouseGestures.hs b/XMonad/Actions/MouseGestures.hs
index 8c56afb1..fd01b936 100644
--- a/XMonad/Actions/MouseGestures.hs
+++ b/XMonad/Actions/MouseGestures.hs
@@ -21,14 +21,13 @@ module XMonad.Actions.MouseGestures (
     mkCollect
 ) where
 
+import XMonad.Prelude
 import XMonad
 import XMonad.Util.Types (Direction2D(..))
 
 import Data.IORef
 import qualified Data.Map as M
 import Data.Map (Map)
-import Data.Maybe
-import Control.Monad
 
 -- $usage
 --
diff --git a/XMonad/Actions/Navigation2D.hs b/XMonad/Actions/Navigation2D.hs
index fc77a129..f2732aaf 100644
--- a/XMonad/Actions/Navigation2D.hs
+++ b/XMonad/Actions/Navigation2D.hs
@@ -57,11 +57,10 @@ module XMonad.Actions.Navigation2D ( -- * Usage
                                    , Direction2D(..)
                                    ) where
 
-import Control.Applicative
 import qualified Data.List as L
 import qualified Data.Map as M
-import Data.Maybe
 import Data.Ord (comparing)
+import XMonad.Prelude
 import XMonad hiding (Screen)
 import qualified XMonad.StackSet as W
 import qualified XMonad.Util.ExtensibleState as XS
@@ -890,10 +889,6 @@ swap win winset = W.focusWindow cur
 centerOf :: Rectangle -> (Position, Position)
 centerOf r = (rect_x r + fi (rect_width r) `div` 2, rect_y r + fi (rect_height r) `div` 2)
 
--- | Shorthand for integer conversions
-fi :: (Integral a, Num b) => a -> b
-fi = fromIntegral
-
 -- | Functions to choose the subset of windows to operate on
 thisLayer, otherLayer :: a -> a -> a
 thisLayer  = curry fst
diff --git a/XMonad/Actions/OnScreen.hs b/XMonad/Actions/OnScreen.hs
index 41c3c349..92dd5d9d 100644
--- a/XMonad/Actions/OnScreen.hs
+++ b/XMonad/Actions/OnScreen.hs
@@ -26,12 +26,9 @@ module XMonad.Actions.OnScreen (
     ) where
 
 import XMonad
+import XMonad.Prelude (fromMaybe, guard)
 import XMonad.StackSet hiding (new)
 
-import Control.Monad (guard)
--- import Control.Monad.State.Class (gets)
-import Data.Maybe (fromMaybe)
-
 
 -- | Focus data definitions
 data Focus = FocusNew                       -- ^ always focus the new screen
diff --git a/XMonad/Actions/PhysicalScreens.hs b/XMonad/Actions/PhysicalScreens.hs
index ce54d132..ac83bd24 100644
--- a/XMonad/Actions/PhysicalScreens.hs
+++ b/XMonad/Actions/PhysicalScreens.hs
@@ -30,11 +30,9 @@ module XMonad.Actions.PhysicalScreens (
                                       ) where
 
 import XMonad
+import XMonad.Prelude (findIndex, on, sortBy)
 import qualified XMonad.StackSet as W
 
-import Data.List (sortBy,findIndex)
-import Data.Function (on)
-
 {- $usage
 
 This module allows you name Xinerama screens from XMonad using their
diff --git a/XMonad/Actions/Plane.hs b/XMonad/Actions/Plane.hs
index 46684bf4..862eaaf4 100644
--- a/XMonad/Actions/Plane.hs
+++ b/XMonad/Actions/Plane.hs
@@ -38,11 +38,9 @@ module XMonad.Actions.Plane
     )
     where
 
-import Control.Monad
-import Data.List
 import Data.Map hiding (split)
-import Data.Maybe
 
+import XMonad.Prelude
 import XMonad
 import XMonad.StackSet hiding (workspaces)
 import XMonad.Util.Run
diff --git a/XMonad/Actions/Prefix.hs b/XMonad/Actions/Prefix.hs
index 59aa39f8..0155d7e8 100644
--- a/XMonad/Actions/Prefix.hs
+++ b/XMonad/Actions/Prefix.hs
@@ -32,9 +32,8 @@ module XMonad.Actions.Prefix
        ) where
 
 import qualified Data.Map as M
-import Data.Maybe
-import Control.Monad (liftM2)
 
+import XMonad.Prelude
 import XMonad
 import XMonad.Util.ExtensibleState as XS
 import XMonad.Util.Paste (sendKey)
diff --git a/XMonad/Actions/RotateSome.hs b/XMonad/Actions/RotateSome.hs
index bff31ad1..c9082752 100644
--- a/XMonad/Actions/RotateSome.hs
+++ b/XMonad/Actions/RotateSome.hs
@@ -25,7 +25,7 @@ module XMonad.Actions.RotateSome (
   ) where
 
 import Control.Arrow ((***))
-import Data.List (partition, sortOn, (\\))
+import XMonad.Prelude (partition, sortOn, (\\))
 import qualified Data.Map as M
 import XMonad (Window, WindowSpace, Rectangle, X, runLayout, screenRect, windows, withWindowSet)
 import XMonad.StackSet (Screen (Screen), Stack (Stack), current, floating, modify', stack)
diff --git a/XMonad/Actions/Search.hs b/XMonad/Actions/Search.hs
index bfbde3e8..f5f37650 100644
--- a/XMonad/Actions/Search.hs
+++ b/XMonad/Actions/Search.hs
@@ -65,13 +65,12 @@ module XMonad.Actions.Search (   -- * Usage
                           ) where
 
 import           Codec.Binary.UTF8.String (encode)
-import           Data.Char                (isAlphaNum, isAscii)
-import           Data.List                (isPrefixOf)
 import           Text.Printf
 import           XMonad                   (X (), liftIO)
 import           XMonad.Prompt            (XPConfig (), XPrompt (showXPrompt, nextCompletion, commandToComplete),
                                            getNextCompletion,
                                            historyCompletionP, mkXPrompt)
+import           XMonad.Prelude           (isAlphaNum, isAscii, isPrefixOf)
 import           XMonad.Prompt.Shell      (getBrowser)
 import           XMonad.Util.Run          (safeSpawn)
 import           XMonad.Util.XSelection   (getSelection)
diff --git a/XMonad/Actions/ShowText.hs b/XMonad/Actions/ShowText.hs
index e7eb8ffb..3737f5ae 100644
--- a/XMonad/Actions/ShowText.hs
+++ b/XMonad/Actions/ShowText.hs
@@ -23,11 +23,10 @@ module XMonad.Actions.ShowText
     , ShowTextConfig(..)
     ) where
 
-import Control.Monad (when)
 import Data.Map (Map,empty,insert,lookup)
-import Data.Monoid (All)
 import Prelude hiding (lookup)
 import XMonad
+import XMonad.Prelude (All, fi, when)
 import XMonad.StackSet (current,screen)
 import XMonad.Util.Font (Align(AlignCenter)
                        , initXMF
@@ -37,7 +36,6 @@ import XMonad.Util.Font (Align(AlignCenter)
 import XMonad.Util.Timer (startTimer)
 import XMonad.Util.XUtils (createNewWindow
                          , deleteWindow
-                         , fi
                          , showWindow
                          , paintAndWrite)
 import qualified XMonad.Util.ExtensibleState as ES
diff --git a/XMonad/Actions/SpawnOn.hs b/XMonad/Actions/SpawnOn.hs
index 87f4ab6d..8d170925 100644
--- a/XMonad/Actions/SpawnOn.hs
+++ b/XMonad/Actions/SpawnOn.hs
@@ -29,15 +29,13 @@ module XMonad.Actions.SpawnOn (
 ) where
 
 import Control.Exception (tryJust)
-import Control.Monad (guard)
-import Data.List (isInfixOf)
-import Data.Maybe (isJust)
 import System.IO.Error (isDoesNotExistError)
 import System.IO.Unsafe (unsafePerformIO)
 import System.Posix.Types (ProcessID)
 import Text.Printf (printf)
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 
 import XMonad.Hooks.ManageHelpers
diff --git a/XMonad/Actions/Submap.hs b/XMonad/Actions/Submap.hs
index d4caa26c..e360b0ff 100644
--- a/XMonad/Actions/Submap.hs
+++ b/XMonad/Actions/Submap.hs
@@ -20,10 +20,9 @@ module XMonad.Actions.Submap (
                              submapDefaultWithKey
                             ) where
 import Data.Bits
-import Data.Maybe (fromMaybe)
+import XMonad.Prelude (fix, fromMaybe)
 import XMonad hiding (keys)
 import qualified Data.Map as M
-import Control.Monad.Fix (fix)
 
 {- $usage
 
diff --git a/XMonad/Actions/SwapPromote.hs b/XMonad/Actions/SwapPromote.hs
index 56a32e89..64dc4c70 100644
--- a/XMonad/Actions/SwapPromote.hs
+++ b/XMonad/Actions/SwapPromote.hs
@@ -57,15 +57,13 @@ module XMonad.Actions.SwapPromote
 
 
 import           XMonad
+import           XMonad.Prelude
 import qualified XMonad.StackSet                as W
 import qualified XMonad.Util.ExtensibleState    as XS
 
 import qualified Data.Map                       as M
 import qualified Data.Set                       as S
-import           Data.List
-import           Data.Maybe
 import           Control.Arrow
-import           Control.Monad
 
 
 -- $usage
diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs
index 808f7793..6faf0297 100644
--- a/XMonad/Actions/TagWindows.hs
+++ b/XMonad/Actions/TagWindows.hs
@@ -26,14 +26,12 @@ module XMonad.Actions.TagWindows (
                  TagPrompt,
                  ) where
 
-import Data.List (nub,sortBy)
-import Control.Monad
 import Control.Exception as E
 
-import XMonad.StackSet hiding (filter)
-
-import XMonad.Prompt
 import XMonad hiding (workspaces)
+import XMonad.Prelude
+import XMonad.Prompt
+import XMonad.StackSet hiding (filter)
 
 econst :: Monad m => a -> IOException -> m a
 econst = const . return
diff --git a/XMonad/Actions/TiledWindowDragging.hs b/XMonad/Actions/TiledWindowDragging.hs
index 2fbcbec9..7c4f1aed 100644
--- a/XMonad/Actions/TiledWindowDragging.hs
+++ b/XMonad/Actions/TiledWindowDragging.hs
@@ -19,11 +19,11 @@ module XMonad.Actions.TiledWindowDragging
     dragWindow
   )
 where
+
 import           XMonad
+import           XMonad.Prelude
 import qualified XMonad.StackSet               as W
 import           XMonad.Layout.DraggingVisualizer
-import           Control.Monad
-
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -32,7 +32,7 @@ import           Control.Monad
 -- > import XMonad.Layout.DraggingVisualizer
 --
 -- then edit your 'layoutHook' by adding the draggingVisualizer to your layout:
--- 
+--
 -- > myLayout = draggingVisualizer $ layoutHook def
 --
 -- Then add a mouse binding for 'dragWindow':
@@ -54,10 +54,10 @@ dragWindow window = whenX (isClient window) $ do
 
     mouseDrag
         (\posX posY ->
-          let rect = Rectangle (fInt (fInt winX + (posX - fInt offsetX)))
-                               (fInt (fInt winY + (posY - fInt offsetY)))
-                               (fInt winWidth)
-                               (fInt winHeight)
+          let rect = Rectangle (fi (fi winX + (posX - fi offsetX)))
+                               (fi (fi winY + (posY - fi offsetY)))
+                               (fi winWidth)
+                               (fi winHeight)
           in  sendMessage $ DraggingWindow window rect
         )
         (sendMessage DraggingStopped >> performWindowSwitching window)
@@ -67,13 +67,13 @@ dragWindow window = whenX (isClient window) $ do
 getPointerOffset :: Window -> X (Int, Int)
 getPointerOffset win = do
     (_, _, _, oX, oY, _, _, _) <- withDisplay (\d -> io $ queryPointer d win)
-    return (fInt oX, fInt oY)
+    return (fi oX, fi oY)
 
 -- | return a tuple of windowX, windowY, windowWidth, windowHeight
 getWindowPlacement :: Window -> X (Int, Int, Int, Int)
 getWindowPlacement window = do
     wa <- withDisplay (\d -> io $ getWindowAttributes d window)
-    return (fInt $ wa_x wa, fInt $ wa_y wa, fInt $ wa_width wa, fInt $ wa_height wa)
+    return (fi $ wa_x wa, fi $ wa_y wa, fi $ wa_width wa, fi $ wa_height wa)
 
 
 performWindowSwitching :: Window -> X ()
@@ -91,11 +91,3 @@ performWindowSwitching win = do
     switchEntries a b x | x == a    = b
                         | x == b    = a
                         | otherwise = x
-
-
-
--- | shorthand for fromIntegral
-fInt :: Integral a => Integral b => a -> b
-fInt = fromIntegral
-
-
diff --git a/XMonad/Actions/TopicSpace.hs b/XMonad/Actions/TopicSpace.hs
index 5b592e46..2f0dab71 100644
--- a/XMonad/Actions/TopicSpace.hs
+++ b/XMonad/Actions/TopicSpace.hs
@@ -63,15 +63,12 @@ module XMonad.Actions.TopicSpace
 where
 
 import XMonad
+import XMonad.Prelude
 
 import qualified Data.Map.Strict         as M
 import qualified XMonad.Hooks.DynamicLog as DL
 import qualified XMonad.StackSet         as W
 
-import Control.Applicative (liftA2)
-import Control.Monad (replicateM_, unless, when)
-import Data.List ((\\), elemIndex, nub, sort, sortOn)
-import Data.Maybe (fromJust, fromMaybe, isNothing, listToMaybe)
 import System.IO (hClose, hPutStr)
 
 import XMonad.Prompt (XPConfig)
diff --git a/XMonad/Actions/TreeSelect.hs b/XMonad/Actions/TreeSelect.hs
index 42f4cbbb..4d7ca970 100644
--- a/XMonad/Actions/TreeSelect.hs
+++ b/XMonad/Actions/TreeSelect.hs
@@ -64,13 +64,12 @@ module XMonad.Actions.TreeSelect
 
 import Control.Monad.Reader
 import Control.Monad.State
-import Data.List (find)
-import Data.Maybe
 import Data.Tree
 import Foreign
 import System.IO
 import System.Posix.Process (forkProcess, executeFile)
 import XMonad hiding (liftX)
+import XMonad.Prelude
 import XMonad.StackSet as W
 import XMonad.Util.Font
 import XMonad.Util.NamedWindows
diff --git a/XMonad/Actions/UpdateFocus.hs b/XMonad/Actions/UpdateFocus.hs
index 46d36b04..d69f756d 100644
--- a/XMonad/Actions/UpdateFocus.hs
+++ b/XMonad/Actions/UpdateFocus.hs
@@ -20,9 +20,8 @@ module XMonad.Actions.UpdateFocus (
 ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
-import Control.Monad (when)
-import Data.Monoid
 
 -- $usage
 -- To make the focus update on mouse movement within an unfocused window, add the
diff --git a/XMonad/Actions/UpdatePointer.hs b/XMonad/Actions/UpdatePointer.hs
index 4293f5c4..ced263a7 100644
--- a/XMonad/Actions/UpdatePointer.hs
+++ b/XMonad/Actions/UpdatePointer.hs
@@ -24,12 +24,11 @@ module XMonad.Actions.UpdatePointer
     where
 
 import XMonad
-import XMonad.Util.XUtils (fi)
-import Control.Arrow
-import Control.Monad
+import XMonad.Prelude
 import XMonad.StackSet (member, peek, screenDetail, current)
-import Data.Maybe
-import Control.Exception
+
+import Control.Exception (SomeException, try)
+import Control.Arrow ((&&&), (***))
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -107,4 +106,3 @@ lerp r a b = (1 - r) * realToFrac a + r * realToFrac b
 clip :: Ord a => (a, a) -> a -> a
 clip (lower, upper) x = if x < lower then lower
     else if x > upper then upper else x
-
diff --git a/XMonad/Actions/Warp.hs b/XMonad/Actions/Warp.hs
index 03afbdfc..62c9fb98 100644
--- a/XMonad/Actions/Warp.hs
+++ b/XMonad/Actions/Warp.hs
@@ -22,7 +22,7 @@ module XMonad.Actions.Warp (
                            warpToWindow
                           ) where
 
-import Data.List
+import XMonad.Prelude
 import XMonad
 import XMonad.StackSet as W
 
diff --git a/XMonad/Actions/WindowGo.hs b/XMonad/Actions/WindowGo.hs
index eaf2d9c2..dfb14ecd 100644
--- a/XMonad/Actions/WindowGo.hs
+++ b/XMonad/Actions/WindowGo.hs
@@ -36,10 +36,8 @@ module XMonad.Actions.WindowGo (
                  module XMonad.ManageHook
                 ) where
 
-import Control.Monad
-import Data.Char (toLower)
 import qualified Data.List as L (nub,sortBy)
-import Data.Monoid
+import XMonad.Prelude
 import XMonad (Query(), X(), ManageHook, WindowSet, withWindowSet, runQuery, liftIO, ask)
 import Graphics.X11 (Window)
 import XMonad.ManageHook
diff --git a/XMonad/Actions/WindowMenu.hs b/XMonad/Actions/WindowMenu.hs
index dddcaed2..8f689354 100644
--- a/XMonad/Actions/WindowMenu.hs
+++ b/XMonad/Actions/WindowMenu.hs
@@ -29,7 +29,7 @@ import qualified XMonad.StackSet as W
 import XMonad.Actions.GridSelect
 import XMonad.Layout.Maximize
 import XMonad.Actions.Minimize
-import XMonad.Util.XUtils (fi)
+import XMonad.Prelude (fi)
 
 -- $usage
 --
diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs
index 7a82cf49..56b4467f 100644
--- a/XMonad/Actions/WindowNavigation.hs
+++ b/XMonad/Actions/WindowNavigation.hs
@@ -40,15 +40,14 @@ module XMonad.Actions.WindowNavigation (
                                        ) where
 
 import XMonad
+import XMonad.Prelude (catMaybes, fromMaybe, listToMaybe, sortBy)
 import XMonad.Util.Types (Direction2D(..))
 import qualified XMonad.StackSet as W
 
 import Control.Arrow (second)
 import Data.IORef
-import Data.List (sortBy)
 import Data.Map (Map())
 import qualified Data.Map as M
-import Data.Maybe (catMaybes, fromMaybe, listToMaybe)
 import Data.Ord (comparing)
 import qualified Data.Set as S
 
diff --git a/XMonad/Actions/WithAll.hs b/XMonad/Actions/WithAll.hs
index fa2c30d4..ee3a26d0 100644
--- a/XMonad/Actions/WithAll.hs
+++ b/XMonad/Actions/WithAll.hs
@@ -15,7 +15,7 @@ module XMonad.Actions.WithAll (
     sinkAll, withAll,
     withAll', killAll) where
 
-import Data.Foldable hiding (foldr)
+import XMonad.Prelude hiding (foldr)
 
 import XMonad
 import XMonad.StackSet
diff --git a/XMonad/Actions/WorkspaceNames.hs b/XMonad/Actions/WorkspaceNames.hs
index 49d04759..43e6ee49 100644
--- a/XMonad/Actions/WorkspaceNames.hs
+++ b/XMonad/Actions/WorkspaceNames.hs
@@ -44,6 +44,7 @@ module XMonad.Actions.WorkspaceNames (
     ) where
 
 import XMonad
+import XMonad.Prelude (fromMaybe, isInfixOf, (<&>), (>=>))
 import qualified XMonad.StackSet as W
 import qualified XMonad.Util.ExtensibleState as XS
 
@@ -54,11 +55,7 @@ import XMonad.Prompt (mkXPrompt, XPConfig)
 import XMonad.Prompt.Workspace (Wor(Wor))
 import XMonad.Util.WorkspaceCompare (getSortByIndex)
 
-import Control.Monad ((>=>))
-import Data.Functor ((<&>))
 import qualified Data.Map as M
-import Data.Maybe (fromMaybe)
-import Data.List (isInfixOf)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
@@ -177,7 +174,7 @@ workspaceNamePrompt conf job = do
               (job . toWsId pairs)
   where toWsId pairs name = fromMaybe "" (lookup name pairs)
         contains completions input =
-          return $ filter (Data.List.isInfixOf input) completions
+          return $ filter (isInfixOf input) completions
 
 -- | Workspace list transformation for
 -- 'XMonad.Hooks.EwmhDesktops.ewmhDesktopsLogHookCustom' that exposes
diff --git a/XMonad/Config/Bluetile.hs b/XMonad/Config/Bluetile.hs
index 454e6225..8e94ab1b 100644
--- a/XMonad/Config/Bluetile.hs
+++ b/XMonad/Config/Bluetile.hs
@@ -62,7 +62,7 @@ import qualified XMonad.StackSet as W
 import qualified Data.Map as M
 
 import System.Exit
-import Control.Monad(when)
+import XMonad.Prelude(when)
 
 -- $usage
 -- To use this module, start with the following @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Config/Dmwit.hs b/XMonad/Config/Dmwit.hs
index cee26ecb..bf64520c 100644
--- a/XMonad/Config/Dmwit.hs
+++ b/XMonad/Config/Dmwit.hs
@@ -4,10 +4,7 @@
 module XMonad.Config.Dmwit where
 
 -- system imports
-import Control.Monad
 import Control.Monad.Trans
-import Data.Char
-import Data.List
 import Data.Map (Map, fromList)
 import Data.Ratio
 import Data.Word
@@ -31,6 +28,7 @@ import XMonad.Layout.Grid
 import XMonad.Layout.IndependentScreens
 import XMonad.Layout.Magnifier
 import XMonad.Layout.NoBorders
+import XMonad.Prelude
 import XMonad.Util.Dzen hiding (x, y)
 import XMonad.Util.SpawnOnce
 -- }}}
@@ -111,7 +109,6 @@ fullscreenMPlayer = className =? "MPlayer" --> do
         Just (16 :% 9)  -> viewFullOn 1 "5" win
         _               -> doFloat
     where
-    fi               = fromIntegral :: Dimension -> Double
     approx (n, d)    = approxRational (fi n / fi d) (1/100)
 
 operationOn f s n w = do
diff --git a/XMonad/Config/Mate.hs b/XMonad/Config/Mate.hs
index eeab1708..f676a73e 100644
--- a/XMonad/Config/Mate.hs
+++ b/XMonad/Config/Mate.hs
@@ -31,7 +31,7 @@ import XMonad
 import XMonad.Config.Desktop
 import XMonad.Util.Run (safeSpawn)
 import XMonad.Util.Ungrab
-import Data.Char (toUpper)
+import XMonad.Prelude (toUpper)
 
 import qualified Data.Map as M
 
diff --git a/XMonad/Config/Monad.hs b/XMonad/Config/Monad.hs
index 42940490..316a1a1c 100644
--- a/XMonad/Config/Monad.hs
+++ b/XMonad/Config/Monad.hs
@@ -20,7 +20,7 @@ module XMonad.Config.Monad where
 import XMonad hiding (terminal, keys)
 import qualified XMonad as X
 import Control.Monad.Writer
-import Data.Monoid
+import XMonad.Prelude
 import Data.Accessor
 import Data.Accessor.Basic hiding (set)
 
diff --git a/XMonad/Config/Prime.hs b/XMonad/Config/Prime.hs
index e7b7d7f3..168f0640 100644
--- a/XMonad/Config/Prime.hs
+++ b/XMonad/Config/Prime.hs
@@ -115,7 +115,7 @@ ifThenElse,
 import Prelude hiding ((>>), mod)
 import qualified Prelude as P ((>>=), (>>))
 
-import Data.Monoid (All)
+import XMonad.Prelude (All)
 
 import XMonad hiding (xmonad, XConfig(..))
 import XMonad (XConfig(XConfig))
diff --git a/XMonad/Hooks/CurrentWorkspaceOnTop.hs b/XMonad/Hooks/CurrentWorkspaceOnTop.hs
index 5b94a8d6..bbedc5fa 100644
--- a/XMonad/Hooks/CurrentWorkspaceOnTop.hs
+++ b/XMonad/Hooks/CurrentWorkspaceOnTop.hs
@@ -25,7 +25,7 @@ module XMonad.Hooks.CurrentWorkspaceOnTop (
 import XMonad
 import qualified XMonad.StackSet as S
 import qualified XMonad.Util.ExtensibleState as XS
-import Control.Monad(when)
+import XMonad.Prelude(when)
 import qualified Data.Map as M
 
 -- $usage
diff --git a/XMonad/Hooks/DebugEvents.hs b/XMonad/Hooks/DebugEvents.hs
index 341a9287..3accd892 100644
--- a/XMonad/Hooks/DebugEvents.hs
+++ b/XMonad/Hooks/DebugEvents.hs
@@ -24,6 +24,7 @@ import           Prelude
 import           XMonad                               hiding (windowEvent
                                                              ,(-->)
                                                              )
+import           XMonad.Prelude                       hiding (fi, bool)
 
 import           XMonad.Hooks.DebugKeyEvents                 (debugKeyEvents)
 import           XMonad.Util.DebugWindow                     (debugWindow)
@@ -33,15 +34,7 @@ import           XMonad.Util.DebugWindow                     (debugWindow)
 import           Control.Exception                    as E
 import           Control.Monad.State
 import           Control.Monad.Reader
-import           Data.Char                                   (isDigit)
-import           Data.Maybe                                  (fromJust)
-import           Data.List                                   (genericIndex
-                                                             ,genericLength
-                                                             ,unfoldr
-                                                             )
 import           Codec.Binary.UTF8.String
-import           Data.Maybe                                  (fromMaybe)
-import           Data.Monoid
 import           Foreign
 import           Foreign.C.Types
 import           Numeric                                     (showHex)
@@ -286,7 +279,7 @@ newtype Decoder a = Decoder (ReaderT Decode (StateT DecodeState X) a)
 #endif
 
 -- | Retrive, parse, and dump a window property.  As all the high-level property
---   interfaces lose information necessary to decode properties correctly, we 
+--   interfaces lose information necessary to decode properties correctly, we
 --   work at the lowest level available.
 dumpProperty          :: Atom -> String -> Window -> Int -> X String
 dumpProperty a n w i  =  do
@@ -413,8 +406,8 @@ runDecode c s (Decoder p) =  runStateT (runReaderT p c) s
 bytes   :: Int -> Int
 bytes w =  w `div` 8
 
--- | The top level property decoder, for a wide variety of standard ICCCM and 
---   EWMH window properties.  We pass part of the 'ReaderT' as arguments for 
+-- | The top level property decoder, for a wide variety of standard ICCCM and
+--   EWMH window properties.  We pass part of the 'ReaderT' as arguments for
 --   pattern matching.
 dumpProp                                              :: Atom -> String -> Decoder Bool
 
@@ -900,7 +893,7 @@ dumpMwmInfo =  do
   guardType ta $ dumpList' [("flags" ,dumpBits mwmHints,cARDINAL)
                            ,("window",dumpWindow       ,wINDOW  )
                            ]
-             
+
 -- the most common case
 dumpEnum    :: [String] -> Decoder Bool
 dumpEnum ss =  dumpEnum' ss cARDINAL
@@ -1000,7 +993,7 @@ dumpMDPrereg =  do
         append "total size = "
         withIndent 13 dump32
         dumpMDBlocks $ fromIntegral dsc
-    
+
 dumpMDBlocks   :: Int -> Decoder Bool
 dumpMDBlocks _ =  propSimple "(drop site info)" -- @@@ maybe later if needed
 
@@ -1024,7 +1017,7 @@ dumpPercent =  guardType cARDINAL $ do
                  n <- getInt' 32
                  case n of
                    Nothing -> return False
-                   Just n' -> 
+                   Just n' ->
                        let pct = 100 * fromIntegral n' / fromIntegral (maxBound :: Word32)
                            pct :: Double
                         in append $ show (round pct :: Integer) ++ "%"
diff --git a/XMonad/Hooks/DebugKeyEvents.hs b/XMonad/Hooks/DebugKeyEvents.hs
index e8789e0d..0b40cee9 100644
--- a/XMonad/Hooks/DebugKeyEvents.hs
+++ b/XMonad/Hooks/DebugKeyEvents.hs
@@ -19,6 +19,7 @@ module XMonad.Hooks.DebugKeyEvents (-- * Usage
                                    ) where
 
 import           XMonad.Core
+import           XMonad.Prelude
 import           XMonad.Operations               (cleanMask)
 
 import           Graphics.X11.Xlib
@@ -26,8 +27,6 @@ import           Graphics.X11.Xlib.Extras
 
 import           Control.Monad.State             (gets)
 import           Data.Bits
-import           Data.List                       (intercalate)
-import           Data.Monoid
 import           Numeric                         (showHex)
 import           System.IO                       (hPutStrLn
                                                  ,stderr)
diff --git a/XMonad/Hooks/DebugStack.hs b/XMonad/Hooks/DebugStack.hs
index bb426966..0779d20a 100644
--- a/XMonad/Hooks/DebugStack.hs
+++ b/XMonad/Hooks/DebugStack.hs
@@ -24,6 +24,7 @@ module XMonad.Hooks.DebugStack (debugStack
                                ) where
 
 import           XMonad.Core
+import           XMonad.Prelude
 import qualified XMonad.StackSet                                       as W
 
 import           XMonad.Util.DebugWindow
@@ -31,10 +32,7 @@ import           XMonad.Util.DebugWindow
 import           Graphics.X11.Types                  (Window)
 import           Graphics.X11.Xlib.Extras            (Event)
 
-import           Control.Monad                       (foldM)
 import           Data.Map                            (member)
-import           Data.Monoid                         (All(..))
-import           Data.List                           (intercalate)
 
 -- | Print the state of the current window stack for the current workspace to
 --   @stderr@, which for most installations goes to @~/.xsession-errors@.
diff --git a/XMonad/Hooks/DynamicBars.hs b/XMonad/Hooks/DynamicBars.hs
index 6582bbec..d346478f 100644
--- a/XMonad/Hooks/DynamicBars.hs
+++ b/XMonad/Hooks/DynamicBars.hs
@@ -29,15 +29,9 @@ module XMonad.Hooks.DynamicBars (
 
 import Prelude
 
-import Control.Monad
 import Control.Monad.Trans (lift)
 import Control.Monad.Writer (WriterT, execWriterT, tell)
 
-import Data.List
-import Data.Maybe
-import Data.Monoid
-import Data.Foldable (traverse_)
-
 import Graphics.X11.Xinerama
 import Graphics.X11.Xlib
 import Graphics.X11.Xlib.Extras
@@ -46,6 +40,7 @@ import Graphics.X11.Xrandr
 import System.IO
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 import XMonad.Hooks.DynamicLog
 import qualified XMonad.Util.ExtensibleState as XS
diff --git a/XMonad/Hooks/DynamicHooks.hs b/XMonad/Hooks/DynamicHooks.hs
index a2a0b7e9..d3a96ffd 100644
--- a/XMonad/Hooks/DynamicHooks.hs
+++ b/XMonad/Hooks/DynamicHooks.hs
@@ -23,12 +23,9 @@ module XMonad.Hooks.DynamicHooks (
   ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.Util.ExtensibleState as XS
 
-import Data.List
-import Data.Maybe (listToMaybe)
-import Data.Monoid
-
 -- $usage
 -- Provides two new kinds of 'ManageHooks' that can be defined at runtime.
 --
diff --git a/XMonad/Hooks/DynamicIcons.hs b/XMonad/Hooks/DynamicIcons.hs
index 18c271d5..b1861659 100644
--- a/XMonad/Hooks/DynamicIcons.hs
+++ b/XMonad/Hooks/DynamicIcons.hs
@@ -33,9 +33,7 @@ import qualified XMonad.StackSet as S
 import qualified Data.Map as M
 
 import XMonad.Hooks.DynamicLog
-import Data.Functor ((<&>))
-import Data.Traversable (for)
-import Control.Monad ((<=<), (>=>))
+import XMonad.Prelude (for, (<&>), (<=<), (>=>))
 
 -- $usage
 -- Dynamically augment Workspace's 'WorkspaceId' as shown on a status bar
diff --git a/XMonad/Hooks/DynamicProperty.hs b/XMonad/Hooks/DynamicProperty.hs
index b6b60953..85e2234c 100644
--- a/XMonad/Hooks/DynamicProperty.hs
+++ b/XMonad/Hooks/DynamicProperty.hs
@@ -26,8 +26,7 @@
 module XMonad.Hooks.DynamicProperty where
 
 import XMonad
-import Data.Monoid
-import Control.Monad (when)
+import XMonad.Prelude
 
 -- |
 -- Run a 'ManageHook' when a specific property is changed on a window. Note
@@ -36,7 +35,7 @@ import Control.Monad (when)
 -- their titles on the fly!):
 --
 -- dynamicPropertyChange "WM_NAME" (className =? "Iceweasel" <&&> title =? "whatever" --> doShift "2")
--- 
+--
 -- Note that the fixity of (-->) won't allow it to be mixed with ($), so you
 -- can't use the obvious $ shorthand.
 --
@@ -46,9 +45,9 @@ import Control.Monad (when)
 -- other 'ManageHook':
 --
 -- >      , handleEventHook = dynamicPropertyChange "WM_NAME" myDynHook <+> handleEventHook baseConfig
--- > 
+-- >
 -- >    {- ... -}
--- > 
+-- >
 -- >    myDynHook = composeAll [...]
 --
 dynamicPropertyChange :: String -> ManageHook -> Event -> X All
diff --git a/XMonad/Hooks/EwmhDesktops.hs b/XMonad/Hooks/EwmhDesktops.hs
index 2f494063..7c82c8bd 100644
--- a/XMonad/Hooks/EwmhDesktops.hs
+++ b/XMonad/Hooks/EwmhDesktops.hs
@@ -33,18 +33,14 @@ module XMonad.Hooks.EwmhDesktops (
 
 import Codec.Binary.UTF8.String (encode)
 import Data.Bits
-import Data.List
-import Data.Maybe
-import Data.Monoid
 import qualified Data.Map.Strict as M
 
 import XMonad
-import Control.Monad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 
 import XMonad.Hooks.SetWMName
 import qualified XMonad.Util.ExtensibleState as E
-import XMonad.Util.XUtils (fi)
 import XMonad.Util.WorkspaceCompare
 import XMonad.Util.WindowProperties (getProp32)
 import qualified XMonad.Util.ExtensibleState as XS
diff --git a/XMonad/Hooks/FadeInactive.hs b/XMonad/Hooks/FadeInactive.hs
index cb7bc412..b3a0f9b0 100644
--- a/XMonad/Hooks/FadeInactive.hs
+++ b/XMonad/Hooks/FadeInactive.hs
@@ -27,9 +27,8 @@ module XMonad.Hooks.FadeInactive (
     ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
-import Control.Applicative (liftA2)
-import Control.Monad
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Hooks/FadeWindows.hs b/XMonad/Hooks/FadeWindows.hs
index 6c866e7f..29bc81f3 100644
--- a/XMonad/Hooks/FadeWindows.hs
+++ b/XMonad/Hooks/FadeWindows.hs
@@ -49,6 +49,7 @@ module XMonad.Hooks.FadeWindows (-- * Usage
                                 ) where
 
 import           XMonad.Core
+import           XMonad.Prelude
 import           XMonad.ManageHook                       (liftX)
 import qualified XMonad.StackSet             as W
 
@@ -56,12 +57,10 @@ import           XMonad.Hooks.FadeInactive               (setOpacity
                                                          ,isUnfocused
                                                          )
 
-import           Control.Monad                           (forM_)
 import           Control.Monad.Reader                    (ask
                                                          ,asks)
 import           Control.Monad.State                     (gets)
 import qualified Data.Map                    as M
-import           Data.Monoid
 
 import           Graphics.X11.Xlib.Extras                (Event(..))
 
diff --git a/XMonad/Hooks/Focus.hs b/XMonad/Hooks/Focus.hs
index 304d8826..a9b60bb3 100644
--- a/XMonad/Hooks/Focus.hs
+++ b/XMonad/Hooks/Focus.hs
@@ -62,14 +62,11 @@ module XMonad.Hooks.Focus
     )
   where
 
-import Data.Maybe
-import Data.Monoid
-import qualified Data.Semigroup as S
-import Control.Monad
+import Control.Arrow ((&&&))
 import Control.Monad.Reader
-import Control.Arrow hiding ((<+>))
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 import qualified XMonad.Util.ExtensibleState as XS
 import XMonad.Hooks.ManageHelpers (currentWs)
@@ -385,8 +382,8 @@ instance MonadReader Focus FocusQuery where
     local f (FocusQuery mx) = FocusQuery (local f mx)
 instance MonadIO FocusQuery where
     liftIO mx       = FocusQuery (liftIO mx)
-instance S.Semigroup a => S.Semigroup (FocusQuery a) where
-    (<>)            = liftM2 (S.<>)
+instance Semigroup a => Semigroup (FocusQuery a) where
+    (<>)            = liftM2 (<>)
 instance Monoid a => Monoid (FocusQuery a) where
     mempty          = return mempty
     mappend         = (<>)
@@ -577,4 +574,3 @@ activateOnCurrentWs = manageFocus (liftQuery activated <&&> newOnCur --> switchF
 activateOnCurrentKeepFocus :: ManageHook
 activateOnCurrentKeepFocus  = manageFocus (liftQuery activated <&&> newOnCur --> keepFocus)
                         <+> activateOnCurrent'
-
diff --git a/XMonad/Hooks/InsertPosition.hs b/XMonad/Hooks/InsertPosition.hs
index ab123d3f..ef670a2d 100644
--- a/XMonad/Hooks/InsertPosition.hs
+++ b/XMonad/Hooks/InsertPosition.hs
@@ -21,10 +21,8 @@ module XMonad.Hooks.InsertPosition (
     ) where
 
 import XMonad(ManageHook, MonadReader(ask))
+import XMonad.Prelude (Endo (Endo), find, fromMaybe)
 import qualified XMonad.StackSet as W
-import Data.Maybe(fromMaybe)
-import Data.List(find)
-import Data.Monoid(Endo(Endo))
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Hooks/ManageDebug.hs b/XMonad/Hooks/ManageDebug.hs
index acfb058c..abb9e963 100644
--- a/XMonad/Hooks/ManageDebug.hs
+++ b/XMonad/Hooks/ManageDebug.hs
@@ -29,11 +29,11 @@ module XMonad.Hooks.ManageDebug (debugManageHook
                                 ) where
 
 import           XMonad
+import           XMonad.Prelude (when)
 import           XMonad.Hooks.DebugStack
 import           XMonad.Util.DebugWindow
 import           XMonad.Util.EZConfig
 import qualified XMonad.Util.ExtensibleState                                                 as XS
-import           Control.Monad                            (when)
 
 -- persistent state for manageHook debugging to trigger logHook debugging
 data ManageStackDebug = MSD (Bool,Bool) deriving Typeable
diff --git a/XMonad/Hooks/ManageDocks.hs b/XMonad/Hooks/ManageDocks.hs
index 69a1dac6..01d1a51f 100644
--- a/XMonad/Hooks/ManageDocks.hs
+++ b/XMonad/Hooks/ManageDocks.hs
@@ -39,14 +39,11 @@ import Foreign.C.Types (CLong)
 import XMonad.Layout.LayoutModifier
 import XMonad.Util.Types
 import XMonad.Util.WindowProperties (getProp32s)
-import XMonad.Util.XUtils (fi)
 import qualified XMonad.Util.ExtensibleState as XS
-import Data.Monoid (All(..))
+import XMonad.Prelude (All (..), fi, filterM, foldlM, void, when, (<=<))
 
 import qualified Data.Set as S
 import qualified Data.Map as M
-import Control.Monad (when, filterM, void, (<=<))
-import Data.Foldable (foldlM)
 
 -- $usage
 -- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Hooks/ManageHelpers.hs b/XMonad/Hooks/ManageHelpers.hs
index e7493f49..c3a98eb9 100644
--- a/XMonad/Hooks/ManageHelpers.hs
+++ b/XMonad/Hooks/ManageHelpers.hs
@@ -59,14 +59,10 @@ module XMonad.Hooks.ManageHelpers (
 ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 import XMonad.Util.WindowProperties (getProp32s)
 
-import Control.Monad (filterM)
-import Data.List ((\\))
-import Data.Maybe
-import Data.Monoid
-
 import System.Posix (ProcessID)
 
 -- | Denotes a side of a screen. @S@ stands for South, @NE@ for Northeast
diff --git a/XMonad/Hooks/Minimize.hs b/XMonad/Hooks/Minimize.hs
index 633f757e..21994cca 100644
--- a/XMonad/Hooks/Minimize.hs
+++ b/XMonad/Hooks/Minimize.hs
@@ -19,11 +19,9 @@ module XMonad.Hooks.Minimize
       minimizeEventHook
     ) where
 
-import Data.Monoid
-import Control.Monad(when)
-
 import XMonad
 import XMonad.Actions.Minimize
+import XMonad.Prelude
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Hooks/Place.hs b/XMonad/Hooks/Place.hs
index e1138ce2..5f6c4f06 100644
--- a/XMonad/Hooks/Place.hs
+++ b/XMonad/Hooks/Place.hs
@@ -34,18 +34,14 @@ module XMonad.Hooks.Place   ( -- * Usage
 
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as S
 
 import XMonad.Layout.WindowArranger
 import XMonad.Actions.FloatKeys
-import XMonad.Util.XUtils
 
 import qualified Data.Map as M
 import Data.Ratio ((%))
-import Data.List (sortBy, minimumBy, partition)
-import Data.Maybe (fromMaybe, catMaybes)
-import Data.Monoid (Endo(..))
-import Control.Monad (guard, join)
 import Control.Monad.Trans (lift)
 
 -- $usage
diff --git a/XMonad/Hooks/PositionStoreHooks.hs b/XMonad/Hooks/PositionStoreHooks.hs
index ba428607..a686a6a8 100644
--- a/XMonad/Hooks/PositionStoreHooks.hs
+++ b/XMonad/Hooks/PositionStoreHooks.hs
@@ -34,15 +34,13 @@ module XMonad.Hooks.PositionStoreHooks (
     ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 import XMonad.Util.PositionStore
 import XMonad.Hooks.ManageDocks
 import XMonad.Layout.Decoration
 
 import System.Random(randomRIO)
-import Control.Monad(when)
-import Data.Maybe
-import Data.Monoid
 import qualified Data.Set as S
 
 -- $usage
diff --git a/XMonad/Hooks/RefocusLast.hs b/XMonad/Hooks/RefocusLast.hs
index f1abd0fa..101cf0d0 100644
--- a/XMonad/Hooks/RefocusLast.hs
+++ b/XMonad/Hooks/RefocusLast.hs
@@ -45,16 +45,13 @@ module XMonad.Hooks.RefocusLast (
 ) where
 
 import XMonad
+import XMonad.Prelude (All (..), asum, fromMaybe, when)
 import qualified XMonad.StackSet as W
 import qualified XMonad.Util.ExtensibleState as XS
 import XMonad.Util.Stack (findS, mapZ_)
 import XMonad.Layout.LayoutModifier
 
-import Data.Maybe (fromMaybe)
-import Data.Monoid (All(..))
-import Data.Foldable (asum)
 import qualified Data.Map.Strict as M
-import Control.Monad (when)
 
 -- }}}
 
@@ -292,4 +289,3 @@ withRecents :: (Window -> Window -> X ()) -> X ()
 withRecents f = withWindowSet $ \ws -> withRecentsIn (W.currentTag ws) () f
 
 -- }}}
-
diff --git a/XMonad/Hooks/RestoreMinimized.hs b/XMonad/Hooks/RestoreMinimized.hs
index 0f664fa5..97352d38 100644
--- a/XMonad/Hooks/RestoreMinimized.hs
+++ b/XMonad/Hooks/RestoreMinimized.hs
@@ -22,7 +22,7 @@ module XMonad.Hooks.RestoreMinimized
     , restoreMinimizedEventHook
     ) where
 
-import Data.Monoid
+import XMonad.Prelude
 
 import XMonad
 
diff --git a/XMonad/Hooks/ScreenCorners.hs b/XMonad/Hooks/ScreenCorners.hs
index 5b0a7a9c..43121a1b 100644
--- a/XMonad/Hooks/ScreenCorners.hs
+++ b/XMonad/Hooks/ScreenCorners.hs
@@ -30,10 +30,8 @@ module XMonad.Hooks.ScreenCorners
     , screenCornerLayoutHook
     ) where
 
-import Data.Monoid
-import Data.List (find)
+import XMonad.Prelude
 import XMonad
-import XMonad.Util.XUtils (fi)
 import XMonad.Layout.LayoutModifier
 
 import qualified Data.Map as M
diff --git a/XMonad/Hooks/ServerMode.hs b/XMonad/Hooks/ServerMode.hs
index f2225239..64d11a38 100644
--- a/XMonad/Hooks/ServerMode.hs
+++ b/XMonad/Hooks/ServerMode.hs
@@ -26,12 +26,10 @@ module XMonad.Hooks.ServerMode
     , serverModeEventHookF
     ) where
 
-import Control.Monad (when)
-import Data.Maybe
-import Data.Monoid
 import System.IO
 
 import XMonad
+import XMonad.Prelude
 import XMonad.Actions.Commands
 
 -- $usage
@@ -47,7 +45,7 @@ import XMonad.Actions.Commands
 -- in stderr (so that you can read it in @~\/.xsession-errors@). Uses "XMonad.Actions.Commands#defaultCommands" as the default.
 --
 -- > main = xmonad def { handleEventHook = serverModeEventHook }
--- 
+--
 -- > xmonadctl 0 # tells xmonad to output command list
 -- > xmonadctl 1 # tells xmonad to switch to workspace 1
 --
diff --git a/XMonad/Hooks/SetWMName.hs b/XMonad/Hooks/SetWMName.hs
index 6ba405f1..13f2132d 100644
--- a/XMonad/Hooks/SetWMName.hs
+++ b/XMonad/Hooks/SetWMName.hs
@@ -41,15 +41,11 @@ module XMonad.Hooks.SetWMName (
     )
   where
 
-import Control.Monad (join)
-import Data.Char (ord)
-import Data.List (nub)
-import Data.Maybe (fromJust, listToMaybe, maybeToList)
 import Foreign.C.Types (CChar)
-
 import Foreign.Marshal.Alloc (alloca)
 
 import XMonad
+import XMonad.Prelude (fromJust, join, listToMaybe, maybeToList, nub, ord)
 
 -- | sets WM name
 setWMName :: String -> X ()
@@ -117,4 +113,3 @@ getSupportWindow = withDisplay $ \dpy -> do
 -- | Get WM name.
 getWMName :: X String
 getWMName = getSupportWindow >>= runQuery title
-
diff --git a/XMonad/Hooks/StatusBar.hs b/XMonad/Hooks/StatusBar.hs
index ac526de8..b22cef19 100644
--- a/XMonad/Hooks/StatusBar.hs
+++ b/XMonad/Hooks/StatusBar.hs
@@ -53,7 +53,6 @@ module XMonad.Hooks.StatusBar (
   ) where
 
 import Control.Exception (SomeException, try)
-import Control.Monad (void)
 import qualified Codec.Binary.UTF8.String as UTF8 (encode)
 import System.Posix.Signals (sigTERM, signalProcessGroup)
 import System.Posix.Types (ProcessID)
@@ -63,6 +62,7 @@ import qualified Data.Map        as M
 import Foreign.C (CChar)
 
 import XMonad
+import XMonad.Prelude (void)
 
 import XMonad.Util.Run
 import qualified XMonad.Util.ExtensibleState as XS
diff --git a/XMonad/Hooks/StatusBar/PP.hs b/XMonad/Hooks/StatusBar/PP.hs
index 3be922d8..b6e47b71 100644
--- a/XMonad/Hooks/StatusBar/PP.hs
+++ b/XMonad/Hooks/StatusBar/PP.hs
@@ -1,5 +1,5 @@
 {-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE NamedFieldPuns      #-}
+{-# LANGUAGE PatternGuards       #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  XMonad.Hooks.StatusBar.PP
@@ -46,15 +46,10 @@ module XMonad.Hooks.StatusBar.PP (
 
     ) where
 
-import Control.Applicative (liftA2)
-import Control.Monad (msum)
-import Data.Char (isSpace)
-import Data.List (intercalate, isPrefixOf, sortOn, stripPrefix)
-import Data.Maybe (catMaybes, fromMaybe, isJust, mapMaybe)
-
 import qualified XMonad.StackSet as S
 
 import XMonad
+import XMonad.Prelude
 
 import XMonad.Util.NamedWindows
 import XMonad.Util.WorkspaceCompare
diff --git a/XMonad/Hooks/ToggleHook.hs b/XMonad/Hooks/ToggleHook.hs
index 225dad47..b926a208 100644
--- a/XMonad/Hooks/ToggleHook.hs
+++ b/XMonad/Hooks/ToggleHook.hs
@@ -39,9 +39,9 @@ module XMonad.Hooks.ToggleHook ( -- * Usage
 import Prelude hiding (all)
 
 import XMonad
+import XMonad.Prelude (guard, join)
 import qualified XMonad.Util.ExtensibleState as XS
 
-import Control.Monad (join,guard)
 import Control.Arrow (first, second)
 
 import Data.Map
diff --git a/XMonad/Hooks/UrgencyHook.hs b/XMonad/Hooks/UrgencyHook.hs
index 2109a7ea..b61d8520 100644
--- a/XMonad/Hooks/UrgencyHook.hs
+++ b/XMonad/Hooks/UrgencyHook.hs
@@ -70,6 +70,7 @@ module XMonad.Hooks.UrgencyHook (
                                  ) where
 
 import XMonad
+import XMonad.Prelude (delete, fromMaybe, listToMaybe, maybeToList, when, (\\))
 import qualified XMonad.StackSet as W
 
 import XMonad.Hooks.ManageHelpers (windowTag)
@@ -79,10 +80,7 @@ import XMonad.Util.NamedWindows (getName)
 import XMonad.Util.Timer (TimerId, startTimer, handleTimer)
 import XMonad.Util.WindowProperties (getProp32)
 
-import Control.Monad (when)
 import Data.Bits (testBit)
-import Data.List (delete, (\\))
-import Data.Maybe (listToMaybe, maybeToList, fromMaybe)
 import qualified Data.Set as S
 import System.IO (hPutStrLn, stderr)
 import Foreign.C.Types (CLong)
diff --git a/XMonad/Hooks/WallpaperSetter.hs b/XMonad/Hooks/WallpaperSetter.hs
index 25fcad21..2e8e54c4 100644
--- a/XMonad/Hooks/WallpaperSetter.hs
+++ b/XMonad/Hooks/WallpaperSetter.hs
@@ -24,6 +24,7 @@ module XMonad.Hooks.WallpaperSetter (
   -- $todo
 ) where
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as S
 import qualified XMonad.Util.ExtensibleState as XS
 
@@ -34,13 +35,8 @@ import System.FilePath ((</>))
 import System.Random (randomRIO)
 
 import qualified Data.Map as M
-import Data.List (sortBy)
-import Data.Char (isAlphaNum)
 import Data.Ord (comparing)
 
-import Control.Monad
-import Data.Maybe
-
 -- $usage
 -- This module requires imagemagick and feh to be installed, as these are utilized
 -- for the required image transformations and the actual setting of the wallpaper.
diff --git a/XMonad/Hooks/WindowSwallowing.hs b/XMonad/Hooks/WindowSwallowing.hs
index d300c173..f7672d02 100644
--- a/XMonad/Hooks/WindowSwallowing.hs
+++ b/XMonad/Hooks/WindowSwallowing.hs
@@ -44,14 +44,12 @@ module XMonad.Hooks.WindowSwallowing
   )
 where
 import           XMonad
+import           XMonad.Prelude
 import qualified XMonad.StackSet               as W
 import qualified XMonad.Util.ExtensibleState   as XS
 import           XMonad.Util.WindowProperties
 import           XMonad.Util.Run                ( runProcessWithInput )
-import           Data.Semigroup                 ( All(..) )
 import qualified Data.Map.Strict               as M
-import           Data.List                      ( isInfixOf )
-import           Control.Monad                  ( when )
 
 -- $usage
 -- You can use this module by including  the following in your @~\/.xmonad/xmonad.hs@:
@@ -237,9 +235,3 @@ instance ExtensionClass SwallowingState where
                                  , stackBeforeWindowClosing = Nothing
                                  , floatingBeforeClosing    = mempty
                                  }
-
-
-fi :: (Integral a, Num b) => a -> b
-fi = fromIntegral
-
-
diff --git a/XMonad/Hooks/WorkspaceByPos.hs b/XMonad/Hooks/WorkspaceByPos.hs
index 0c58bfc2..44be9ae5 100644
--- a/XMonad/Hooks/WorkspaceByPos.hs
+++ b/XMonad/Hooks/WorkspaceByPos.hs
@@ -21,11 +21,10 @@ module XMonad.Hooks.WorkspaceByPos (
     ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
-import XMonad.Util.XUtils (fi)
 
-import Data.Maybe
-import Control.Monad.Error ((<=<),guard,lift,runErrorT,throwError)
+import Control.Monad.Except (lift, runExceptT, throwError)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -43,7 +42,7 @@ needsMoving :: Window -> X (Maybe WorkspaceId)
 needsMoving w = withDisplay $ \d -> do
     -- only relocate windows with non-zero position
     wa <- io $ getWindowAttributes d w
-    fmap (const Nothing `either` Just) . runErrorT $ do
+    fmap (const Nothing `either` Just) . runExceptT $ do
         guard $ wa_x wa /= 0 || wa_y wa /= 0
         ws <- gets windowset
         sc <- lift $ fromMaybe (W.current ws)
diff --git a/XMonad/Hooks/WorkspaceHistory.hs b/XMonad/Hooks/WorkspaceHistory.hs
index bf8e2942..0cb2af9d 100644
--- a/XMonad/Hooks/WorkspaceHistory.hs
+++ b/XMonad/Hooks/WorkspaceHistory.hs
@@ -34,7 +34,7 @@ import           Prelude
 
 import XMonad
 import XMonad.StackSet hiding (delete, filter, new)
-import Data.List (delete, find, foldl', groupBy, nub, sortBy)
+import XMonad.Prelude (delete, find, foldl', groupBy, nub, sortBy)
 import qualified XMonad.Util.ExtensibleState as XS
 
 -- $usage
diff --git a/XMonad/Hooks/XPropManage.hs b/XMonad/Hooks/XPropManage.hs
index 3a41bf98..5bee71a0 100644
--- a/XMonad/Hooks/XPropManage.hs
+++ b/XMonad/Hooks/XPropManage.hs
@@ -19,12 +19,10 @@ module XMonad.Hooks.XPropManage (
                  ) where
 
 import Control.Exception as E
-import Data.Char (chr)
-import Data.Monoid (Endo(..))
-
 import Control.Monad.Trans (lift)
 
 import XMonad
+import XMonad.Prelude (Endo (..), chr)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/AutoMaster.hs b/XMonad/Layout/AutoMaster.hs
index 6760bbfb..6df2bb5e 100644
--- a/XMonad/Layout/AutoMaster.hs
+++ b/XMonad/Layout/AutoMaster.hs
@@ -20,7 +20,7 @@ module XMonad.Layout.AutoMaster (
                              -- $usage
                              autoMaster, AutoMaster
                             ) where
-import Control.Monad
+import XMonad.Prelude
 
 import XMonad
 import qualified XMonad.StackSet as W
diff --git a/XMonad/Layout/AvoidFloats.hs b/XMonad/Layout/AvoidFloats.hs
index 65215efa..5f20596d 100644
--- a/XMonad/Layout/AvoidFloats.hs
+++ b/XMonad/Layout/AvoidFloats.hs
@@ -26,11 +26,10 @@ module XMonad.Layout.AvoidFloats (
 
 import XMonad
 import XMonad.Layout.LayoutModifier
+import XMonad.Prelude (fi, maximumBy, maybeToList, sortBy)
 import qualified XMonad.StackSet as W
 
-import Data.List
 import Data.Ord
-import Data.Maybe
 import qualified Data.Map as M
 import qualified Data.Set as S
 
@@ -116,7 +115,7 @@ instance LayoutModifier AvoidFloats Window where
             toRect :: WindowAttributes -> Rectangle
             toRect wa = let b = fi $ wa_border_width wa
                         in Rectangle (fi $ wa_x wa) (fi $ wa_y wa) (fi $ wa_width wa + 2*b) (fi $ wa_height wa + 2*b)
-            
+
             bigEnough :: Rectangle -> Bool
             bigEnough rect = rect_width rect >= fi (minw lm) && rect_height rect >= fi (minh lm)
 
@@ -218,9 +217,6 @@ findGaps br rs = let (gaps,end) = foldr findGaps' ([], left br) $ sortBy (flip $
         inBounds :: Rectangle -> Bool
         inBounds r = left r < right br && left br < right r
 
-fi :: (Integral a, Num b) => a -> b
-fi x = fromIntegral x
-
 (?:) :: Maybe a -> [a] -> [a]
 Just x ?: xs = x:xs
 _ ?: xs = xs
diff --git a/XMonad/Layout/BinarySpacePartition.hs b/XMonad/Layout/BinarySpacePartition.hs
index 8aa7c9e1..9db45d46 100644
--- a/XMonad/Layout/BinarySpacePartition.hs
+++ b/XMonad/Layout/BinarySpacePartition.hs
@@ -34,6 +34,7 @@ module XMonad.Layout.BinarySpacePartition (
   ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 import XMonad.Util.Stack hiding (Zipper)
 import XMonad.Util.Types
@@ -45,9 +46,6 @@ import XMonad.Util.XUtils
 
 import qualified Data.Map as M
 import qualified Data.Set as S
-import Data.List ((\\), elemIndex, foldl')
-import Data.Maybe (fromMaybe, isNothing, isJust, mapMaybe, catMaybes)
-import Control.Monad
 import Data.Ratio ((%))
 
 -- $usage
diff --git a/XMonad/Layout/BorderResize.hs b/XMonad/Layout/BorderResize.hs
index 21e7e929..9ffedf9b 100644
--- a/XMonad/Layout/BorderResize.hs
+++ b/XMonad/Layout/BorderResize.hs
@@ -31,7 +31,7 @@ import XMonad
 import XMonad.Layout.Decoration
 import XMonad.Layout.WindowArranger
 import XMonad.Util.XUtils
-import Control.Monad(when)
+import XMonad.Prelude(when)
 import qualified Data.Map as M
 
 -- $usage
diff --git a/XMonad/Layout/BoringWindows.hs b/XMonad/Layout/BoringWindows.hs
index 071fd971..00ff7bb4 100644
--- a/XMonad/Layout/BoringWindows.hs
+++ b/XMonad/Layout/BoringWindows.hs
@@ -36,8 +36,8 @@ import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
                                     LayoutModifier(handleMessOrMaybeModifyIt, redoLayout))
 import XMonad(Typeable, LayoutClass, Message, X, fromMessage,
               broadcastMessage, sendMessage, windows, withFocused, Window)
-import Data.List((\\), union)
-import Data.Maybe(fromMaybe, listToMaybe, maybeToList)
+import XMonad.Prelude (fromMaybe, listToMaybe, maybeToList, union, (\\))
+import XMonad.Util.Stack (reverseS)
 import qualified Data.Map as M
 import qualified XMonad.StackSet as W
 
diff --git a/XMonad/Layout/Circle.hs b/XMonad/Layout/Circle.hs
index f9f09fe1..310ee66f 100644
--- a/XMonad/Layout/Circle.hs
+++ b/XMonad/Layout/Circle.hs
@@ -20,7 +20,7 @@ module XMonad.Layout.Circle (
                              Circle (..)
                             ) where -- actually it's an ellipse
 
-import Data.List
+import XMonad.Prelude
 import XMonad
 import XMonad.StackSet (integrate, peek)
 
diff --git a/XMonad/Layout/Combo.hs b/XMonad/Layout/Combo.hs
index b9ae8ef0..23ee5270 100644
--- a/XMonad/Layout/Combo.hs
+++ b/XMonad/Layout/Combo.hs
@@ -22,9 +22,8 @@ module XMonad.Layout.Combo (
                             CombineTwo
                            ) where
 
-import Data.List ( delete, intersect, (\\) )
-import Data.Maybe ( isJust )
 import XMonad hiding (focus)
+import XMonad.Prelude (delete, intersect, isJust, (\\))
 import XMonad.StackSet ( integrate', Workspace (..), Stack(..) )
 import XMonad.Layout.WindowNavigation ( MoveWindowToWindow(..) )
 import qualified XMonad.StackSet as W ( differentiate )
diff --git a/XMonad/Layout/ComboP.hs b/XMonad/Layout/ComboP.hs
index 884e1212..1ccd53bc 100644
--- a/XMonad/Layout/ComboP.hs
+++ b/XMonad/Layout/ComboP.hs
@@ -24,9 +24,7 @@ module XMonad.Layout.ComboP (
                              Property(..)
                             ) where
 
-import Data.List ( delete, intersect, (\\) )
-import Data.Maybe ( isJust )
-import Control.Monad
+import XMonad.Prelude
 import XMonad hiding (focus)
 import XMonad.StackSet ( Workspace (..), Stack(..) )
 import XMonad.Layout.WindowNavigation
diff --git a/XMonad/Layout/Cross.hs b/XMonad/Layout/Cross.hs
index b1f11121..8217b428 100644
--- a/XMonad/Layout/Cross.hs
+++ b/XMonad/Layout/Cross.hs
@@ -19,7 +19,7 @@ module XMonad.Layout.Cross(
 
 import XMonad( Dimension, Rectangle(..), LayoutClass(..), Resize(..), fromMessage )
 import XMonad.StackSet( focus, up, down )
-import Control.Monad( msum )
+import XMonad.Prelude( msum )
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs
index cacc3a71..7e0e50e1 100644
--- a/XMonad/Layout/Decoration.hs
+++ b/XMonad/Layout/Decoration.hs
@@ -36,12 +36,10 @@ module XMonad.Layout.Decoration
     , DecorationState, OrigWin
     ) where
 
-import Control.Monad (when)
-import Data.Maybe
-import Data.List
 import Foreign.C.Types(CInt)
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 import XMonad.Hooks.UrgencyHook
 import XMonad.Layout.LayoutModifier
diff --git a/XMonad/Layout/DecorationAddons.hs b/XMonad/Layout/DecorationAddons.hs
index b77a4d4f..483fb5d5 100644
--- a/XMonad/Layout/DecorationAddons.hs
+++ b/XMonad/Layout/DecorationAddons.hs
@@ -30,7 +30,7 @@ import XMonad.Hooks.ManageDocks
 import XMonad.Util.Font
 import XMonad.Util.PositionStore
 
-import Data.Maybe
+import XMonad.Prelude
 import qualified Data.Set as S
 
 minimizeButtonOffset :: Int
diff --git a/XMonad/Layout/Dishes.hs b/XMonad/Layout/Dishes.hs
index 805cc724..b7f07342 100644
--- a/XMonad/Layout/Dishes.hs
+++ b/XMonad/Layout/Dishes.hs
@@ -23,7 +23,7 @@ module XMonad.Layout.Dishes (
 
 import XMonad
 import XMonad.StackSet (integrate)
-import Control.Monad (ap)
+import XMonad.Prelude (ap)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/Dwindle.hs b/XMonad/Layout/Dwindle.hs
index a5390c29..0c623bf8 100644
--- a/XMonad/Layout/Dwindle.hs
+++ b/XMonad/Layout/Dwindle.hs
@@ -27,7 +27,7 @@ module XMonad.Layout.Dwindle ( -- * Usage
                              , Chirality(..)
                              ) where
 
-import Data.List ( unfoldr )
+import XMonad.Prelude ( unfoldr )
 import XMonad
 import XMonad.StackSet ( integrate, Stack )
 import XMonad.Util.Types ( Direction2D(..) )
diff --git a/XMonad/Layout/FixedColumn.hs b/XMonad/Layout/FixedColumn.hs
index 00045f4a..b543d3a7 100644
--- a/XMonad/Layout/FixedColumn.hs
+++ b/XMonad/Layout/FixedColumn.hs
@@ -22,8 +22,6 @@ module XMonad.Layout.FixedColumn (
         FixedColumn(..)
 ) where
 
-import Control.Monad (msum)
-import Data.Maybe (fromMaybe)
 import Graphics.X11.Xlib (Window, rect_width)
 import Graphics.X11.Xlib.Extras ( getWMNormalHints
                                 , getWindowAttributes
@@ -31,6 +29,7 @@ import Graphics.X11.Xlib.Extras ( getWMNormalHints
                                 , sh_resize_inc
                                 , wa_border_width)
 
+import XMonad.Prelude (fromMaybe, msum)
 import XMonad.Core (X, LayoutClass(..), fromMessage, io, withDisplay)
 import XMonad.Layout (Resize(..), IncMasterN(..), tile)
 import XMonad.StackSet as W
diff --git a/XMonad/Layout/Fullscreen.hs b/XMonad/Layout/Fullscreen.hs
index fafd1b83..9554d44d 100644
--- a/XMonad/Layout/Fullscreen.hs
+++ b/XMonad/Layout/Fullscreen.hs
@@ -32,6 +32,7 @@ module XMonad.Layout.Fullscreen
     ) where
 
 import           XMonad
+import           XMonad.Prelude
 import           XMonad.Layout.LayoutModifier
 import           XMonad.Layout.NoBorders        (SmartBorder, smartBorders)
 import           XMonad.Hooks.EwmhDesktops      (fullscreenStartup)
@@ -40,11 +41,7 @@ import           XMonad.Util.WindowProperties
 import qualified XMonad.Util.Rectangle          as R
 import qualified XMonad.StackSet                as W
 
-import           Data.List
-import           Data.Maybe
-import           Data.Monoid
 import qualified Data.Map                       as M
-import           Control.Monad
 import           Control.Arrow                  (second)
 
 -- $usage
diff --git a/XMonad/Layout/Gaps.hs b/XMonad/Layout/Gaps.hs
index fc238747..99905749 100644
--- a/XMonad/Layout/Gaps.hs
+++ b/XMonad/Layout/Gaps.hs
@@ -35,14 +35,12 @@ module XMonad.Layout.Gaps (
                           weakModifyGaps, modifyGap, setGaps, setGap
                           ) where
 
+import XMonad.Prelude (delete, fi)
 import XMonad.Core
 import Graphics.X11 (Rectangle(..))
 
 import XMonad.Layout.LayoutModifier
 import XMonad.Util.Types (Direction2D(..))
-import XMonad.Util.XUtils (fi)
-
-import Data.List (delete)
 
 -- $usage
 -- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
diff --git a/XMonad/Layout/GridVariants.hs b/XMonad/Layout/GridVariants.hs
index c0c78d14..dd6c0292 100644
--- a/XMonad/Layout/GridVariants.hs
+++ b/XMonad/Layout/GridVariants.hs
@@ -27,7 +27,7 @@ module XMonad.Layout.GridVariants ( -- * Usage
                                   , Orientation(..)
                                   ) where
 
-import Control.Monad
+import XMonad.Prelude
 import XMonad
 import qualified XMonad.StackSet as W
 
diff --git a/XMonad/Layout/Groups.hs b/XMonad/Layout/Groups.hs
index 7eda99ca..8176777d 100644
--- a/XMonad/Layout/Groups.hs
+++ b/XMonad/Layout/Groups.hs
@@ -54,15 +54,12 @@ module XMonad.Layout.Groups ( -- * Usage
                             ) where
 
 import XMonad
+import XMonad.Prelude hiding (group)
 import qualified XMonad.StackSet as W
 
 import XMonad.Util.Stack
 
-import Data.Maybe (isJust, isNothing, fromMaybe, catMaybes, fromJust)
-import Data.List ((\\))
 import Control.Arrow ((>>>))
-import Control.Applicative ((<|>))
-import Control.Monad (forM,void)
 
 -- $usage
 -- This module provides a layout combinator that allows you
diff --git a/XMonad/Layout/Groups/Helpers.hs b/XMonad/Layout/Groups/Helpers.hs
index c77f1580..76342211 100644
--- a/XMonad/Layout/Groups/Helpers.hs
+++ b/XMonad/Layout/Groups/Helpers.hs
@@ -47,7 +47,7 @@ import qualified XMonad.Layout.Groups as G
 
 import XMonad.Actions.MessageFeedback (sendMessageB)
 
-import Control.Monad (unless)
+import XMonad.Prelude (unless)
 import qualified Data.Map as M
 
 -- $usage
diff --git a/XMonad/Layout/HintedGrid.hs b/XMonad/Layout/HintedGrid.hs
index 5575d733..6ee35317 100644
--- a/XMonad/Layout/HintedGrid.hs
+++ b/XMonad/Layout/HintedGrid.hs
@@ -24,10 +24,10 @@ module XMonad.Layout.HintedGrid (
 import Prelude hiding ((.))
 
 import XMonad
+import XMonad.Prelude (replicateM, sortBy)
 import XMonad.StackSet
 
-import Control.Monad.State
-import Data.List
+import Control.Monad.State (runState)
 import Data.Ord
 
 infixr 9 .
diff --git a/XMonad/Layout/HintedTile.hs b/XMonad/Layout/HintedTile.hs
index fc3a8562..b0d46aa5 100644
--- a/XMonad/Layout/HintedTile.hs
+++ b/XMonad/Layout/HintedTile.hs
@@ -23,7 +23,7 @@ module XMonad.Layout.HintedTile (
 
 import XMonad hiding (Tall(..))
 import qualified XMonad.StackSet as W
-import Control.Monad
+import XMonad.Prelude
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/IfMax.hs b/XMonad/Layout/IfMax.hs
index 1ca8d4a7..bbef89cf 100644
--- a/XMonad/Layout/IfMax.hs
+++ b/XMonad/Layout/IfMax.hs
@@ -8,7 +8,7 @@
 -- Stability   :  unstable
 -- Portability :  unportable
 --
--- Provides IfMax layout, which will run one layout if there are maximum N 
+-- Provides IfMax layout, which will run one layout if there are maximum N
 -- windows on workspace, and another layout, when number of windows is greater
 -- than N.
 --
@@ -23,16 +23,16 @@ module XMonad.Layout.IfMax
     , ifMax
     ) where
 
-import Control.Arrow
+import Control.Arrow ((&&&))
 import qualified Data.List as L
 import qualified Data.Map  as M
-import Data.Maybe
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 
 -- $usage
--- IfMax layout will run one layout if number of windows on workspace is as 
+-- IfMax layout will run one layout if number of windows on workspace is as
 -- maximum N, and else will run another layout.
 --
 -- You can use this module by adding folowing in your @xmonad.hs@:
@@ -91,4 +91,3 @@ ifMax :: (LayoutClass l1 w, LayoutClass l2 w)
       -> l2 w           -- ^ Second layout
       -> IfMax l1 l2 w
 ifMax n l1 l2 = IfMax n l1 l2
-
diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs
index 7117e1eb..bbb3f157 100644
--- a/XMonad/Layout/IndependentScreens.hs
+++ b/XMonad/Layout/IndependentScreens.hs
@@ -29,11 +29,10 @@ module XMonad.Layout.IndependentScreens (
 ) where
 
 -- for the screen stuff
-import Control.Applicative(liftA2)
-import Control.Arrow hiding ((|||))
-import Data.List (nub, genericLength)
+import Control.Arrow ((***))
 import Graphics.X11.Xinerama
 import XMonad
+import XMonad.Prelude
 import XMonad.StackSet hiding (filter, workspaces)
 import XMonad.Hooks.DynamicLog
 
diff --git a/XMonad/Layout/LayoutBuilder.hs b/XMonad/Layout/LayoutBuilder.hs
index a2ada603..22d74323 100644
--- a/XMonad/Layout/LayoutBuilder.hs
+++ b/XMonad/Layout/LayoutBuilder.hs
@@ -57,11 +57,8 @@ module XMonad.Layout.LayoutBuilder (
   LayoutN,
 ) where
 
---------------------------------------------------------------------------------
-import Control.Applicative ((<|>))
-import Control.Monad (foldM)
-import Data.Maybe
 import XMonad
+import XMonad.Prelude (foldM, (<|>), isJust, fromMaybe, isNothing, listToMaybe)
 import qualified XMonad.StackSet as W
 import XMonad.Util.WindowProperties
 
diff --git a/XMonad/Layout/LayoutBuilderP.hs b/XMonad/Layout/LayoutBuilderP.hs
index e74368c1..268f8906 100644
--- a/XMonad/Layout/LayoutBuilderP.hs
+++ b/XMonad/Layout/LayoutBuilderP.hs
@@ -22,10 +22,8 @@ module XMonad.Layout.LayoutBuilderP {-# DEPRECATED "Use XMonad.Layout.LayoutBuil
   Predicate (..), Proxy(..),
   ) where
 
-import Control.Monad
-import Data.Maybe (isJust)
-
 import XMonad
+import XMonad.Prelude hiding (Const)
 import qualified XMonad.StackSet as W
 import XMonad.Util.WindowProperties
 
diff --git a/XMonad/Layout/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs
index c2229b2c..94060a2b 100644
--- a/XMonad/Layout/LayoutCombinators.hs
+++ b/XMonad/Layout/LayoutCombinators.hs
@@ -52,7 +52,7 @@ module XMonad.Layout.LayoutCombinators
     , NewSelect
     ) where
 
-import Data.Maybe ( isJust, isNothing )
+import XMonad.Prelude ( isJust, isNothing )
 
 import XMonad hiding ((|||))
 import XMonad.StackSet (Workspace (..))
diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index 35f1619c..406ea850 100644
--- a/XMonad/Layout/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -29,6 +29,7 @@ import XMonad(LayoutClass(runLayout), mkAdjust, Window,
               X, refresh, Event(..), propertyNotify, wM_NORMAL_HINTS,
               (<&&>), io, applySizeHints, whenX, isClient, withDisplay,
               getWindowAttributes, getWMNormalHints, WindowAttributes(..))
+import XMonad.Prelude (All (..), fromJust, join, on, sortBy)
 import qualified XMonad.StackSet as W
 
 import XMonad.Layout.Decoration(isInStack)
@@ -36,14 +37,9 @@ import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
                                     LayoutModifier(modifyLayout, redoLayout, modifierDescription))
 import XMonad.Util.Types(Direction2D(..))
 import Control.Arrow(Arrow((***), first, second))
-import Control.Monad(join)
-import Data.Function(on)
-import Data.List(sortBy)
-import Data.Monoid(All(..))
 
 import Data.Set (Set)
 import qualified Data.Set as Set
-import Data.Maybe(fromJust)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/LayoutModifier.hs b/XMonad/Layout/LayoutModifier.hs
index a0157801..132ed5b7 100644
--- a/XMonad/Layout/LayoutModifier.hs
+++ b/XMonad/Layout/LayoutModifier.hs
@@ -29,7 +29,7 @@ module XMonad.Layout.LayoutModifier (
     LayoutModifier(..), ModifiedLayout(..)
     ) where
 
-import Control.Monad
+import XMonad.Prelude
 
 import XMonad
 import XMonad.StackSet ( Stack, Workspace (..) )
diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs
index 3a337abc..ea0febe0 100644
--- a/XMonad/Layout/LimitWindows.hs
+++ b/XMonad/Layout/LimitWindows.hs
@@ -37,11 +37,10 @@ module XMonad.Layout.LimitWindows (
     LimitWindows, Selection,
     ) where
 
-import XMonad.Layout.LayoutModifier
 import XMonad
+import XMonad.Layout.LayoutModifier
+import XMonad.Prelude (fromJust, guard, (<=<))
 import qualified XMonad.StackSet as W
-import Control.Monad((<=<),guard)
-import Data.Maybe(fromJust)
 
 -- $usage
 -- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/MagicFocus.hs b/XMonad/Layout/MagicFocus.hs
index ef50c0db..2c90d95d 100644
--- a/XMonad/Layout/MagicFocus.hs
+++ b/XMonad/Layout/MagicFocus.hs
@@ -29,7 +29,7 @@ import qualified XMonad.StackSet as W
 import XMonad.Layout.LayoutModifier
 
 import XMonad.Actions.UpdatePointer (updatePointer)
-import Data.Monoid(All(..))
+import XMonad.Prelude(All(..))
 import qualified Data.Map as M
 
 -- $usage
diff --git a/XMonad/Layout/Magnifier.hs b/XMonad/Layout/Magnifier.hs
index 10812b6d..58de4e8a 100644
--- a/XMonad/Layout/Magnifier.hs
+++ b/XMonad/Layout/Magnifier.hs
@@ -46,13 +46,12 @@ module XMonad.Layout.Magnifier
       Magnifier,
     ) where
 
-import Data.Bool (bool)
 import Numeric.Natural (Natural)
 
 import XMonad
+import XMonad.Prelude (bool, fi)
 import XMonad.Layout.LayoutModifier
 import XMonad.StackSet
-import XMonad.Util.XUtils
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/Maximize.hs b/XMonad/Layout/Maximize.hs
index 4abb12b6..9805117d 100644
--- a/XMonad/Layout/Maximize.hs
+++ b/XMonad/Layout/Maximize.hs
@@ -27,7 +27,7 @@ module XMonad.Layout.Maximize (
 import XMonad
 import qualified XMonad.StackSet as S
 import XMonad.Layout.LayoutModifier
-import Data.List ( partition )
+import XMonad.Prelude ( partition )
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/MessageControl.hs b/XMonad/Layout/MessageControl.hs
index ff125a66..e32fc88b 100644
--- a/XMonad/Layout/MessageControl.hs
+++ b/XMonad/Layout/MessageControl.hs
@@ -122,4 +122,4 @@ unEscape l = ModifiedLayout UE l
 
 ignore :: (Message m, LayoutClass l w)
           => m -> l w -> (Ignore m l w)
-ignore _ l = I l
\ No newline at end of file
+ignore _ l = I l
diff --git a/XMonad/Layout/Monitor.hs b/XMonad/Layout/Monitor.hs
index abd629a3..bf78c2dc 100644
--- a/XMonad/Layout/Monitor.hs
+++ b/XMonad/Layout/Monitor.hs
@@ -32,11 +32,11 @@ module XMonad.Layout.Monitor (
     ) where
 
 import XMonad
+import XMonad.Prelude (unless)
 import XMonad.Layout.LayoutModifier
 import XMonad.Util.WindowProperties
 import XMonad.Hooks.ManageHelpers (doHideIgnore)
 import XMonad.Hooks.FadeInactive (setOpacity)
-import Control.Monad
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/Mosaic.hs b/XMonad/Layout/Mosaic.hs
index 94cbc705..2fc1c250 100644
--- a/XMonad/Layout/Mosaic.hs
+++ b/XMonad/Layout/Mosaic.hs
@@ -32,13 +32,9 @@ import XMonad(Typeable,
               LayoutClass(doLayout, handleMessage, pureMessage, description),
               Message, X, fromMessage, withWindowSet, Resize(..),
               splitHorizontallyBy, splitVerticallyBy, sendMessage, Rectangle)
+import XMonad.Prelude (mplus, on, sortBy, sum)
 import qualified XMonad.StackSet as W
 import Control.Arrow(second, first)
-import Control.Monad(mplus)
-import Data.Foldable(sum)
-import Data.Function(on)
-import Data.List(sortBy)
-
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/MosaicAlt.hs b/XMonad/Layout/MosaicAlt.hs
index b0bc1b40..3e70843c 100644
--- a/XMonad/Layout/MosaicAlt.hs
+++ b/XMonad/Layout/MosaicAlt.hs
@@ -33,7 +33,7 @@ module XMonad.Layout.MosaicAlt (
 import XMonad
 import qualified XMonad.StackSet as W
 import qualified Data.Map as M
-import Data.List ( sortBy )
+import XMonad.Prelude ( sortBy )
 import Data.Ratio
 
 -- $usage
diff --git a/XMonad/Layout/MultiColumns.hs b/XMonad/Layout/MultiColumns.hs
index 3e9321d1..76973a6b 100644
--- a/XMonad/Layout/MultiColumns.hs
+++ b/XMonad/Layout/MultiColumns.hs
@@ -25,7 +25,7 @@ module XMonad.Layout.MultiColumns (
 import XMonad
 import qualified XMonad.StackSet as W
 
-import Control.Monad
+import XMonad.Prelude
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/MultiDishes.hs b/XMonad/Layout/MultiDishes.hs
index 85348782..0a99502e 100644
--- a/XMonad/Layout/MultiDishes.hs
+++ b/XMonad/Layout/MultiDishes.hs
@@ -23,7 +23,7 @@ module XMonad.Layout.MultiDishes (
 
 import XMonad
 import XMonad.StackSet (integrate)
-import Control.Monad (ap)
+import XMonad.Prelude (ap)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/MultiToggle.hs b/XMonad/Layout/MultiToggle.hs
index f7b28c62..437a839b 100644
--- a/XMonad/Layout/MultiToggle.hs
+++ b/XMonad/Layout/MultiToggle.hs
@@ -32,12 +32,12 @@ module XMonad.Layout.MultiToggle (
 ) where
 
 import XMonad
+import XMonad.Prelude hiding (find)
 
 import XMonad.StackSet (Workspace(..))
 
 import Control.Arrow
 import Data.Typeable
-import Data.Maybe
 
 -- $usage
 -- The basic idea is to have a base layout and a set of layout transformers,
diff --git a/XMonad/Layout/NoBorders.hs b/XMonad/Layout/NoBorders.hs
index e08570ce..3a79005d 100644
--- a/XMonad/Layout/NoBorders.hs
+++ b/XMonad/Layout/NoBorders.hs
@@ -34,15 +34,12 @@ module XMonad.Layout.NoBorders ( -- * Usage
                                ) where
 
 import           XMonad
+import           XMonad.Prelude
 import           XMonad.Layout.LayoutModifier
 import qualified XMonad.StackSet                as W
 import qualified XMonad.Util.Rectangle          as R
 
-import           Data.List                      hiding (singleton)
-import           Data.Monoid
 import qualified Data.Map                       as M
-import           Data.Function                  (on)
-import           Control.Monad                  (guard)
 
 
 -- $usage
diff --git a/XMonad/Layout/PerScreen.hs b/XMonad/Layout/PerScreen.hs
index b062dc49..e5645734 100644
--- a/XMonad/Layout/PerScreen.hs
+++ b/XMonad/Layout/PerScreen.hs
@@ -25,7 +25,7 @@ module XMonad.Layout.PerScreen
 import XMonad
 import qualified XMonad.StackSet as W
 
-import Data.Maybe (fromMaybe)
+import XMonad.Prelude (fromMaybe)
 
 -- $usage
 -- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
diff --git a/XMonad/Layout/PerWorkspace.hs b/XMonad/Layout/PerWorkspace.hs
index 1013fe25..ddd25ccd 100644
--- a/XMonad/Layout/PerWorkspace.hs
+++ b/XMonad/Layout/PerWorkspace.hs
@@ -25,7 +25,7 @@ module XMonad.Layout.PerWorkspace
 import XMonad
 import qualified XMonad.StackSet as W
 
-import Data.Maybe (fromMaybe)
+import XMonad.Prelude (fromMaybe)
 
 -- $usage
 -- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
diff --git a/XMonad/Layout/PositionStoreFloat.hs b/XMonad/Layout/PositionStoreFloat.hs
index abdac261..22d8edef 100644
--- a/XMonad/Layout/PositionStoreFloat.hs
+++ b/XMonad/Layout/PositionStoreFloat.hs
@@ -29,9 +29,7 @@ import XMonad
 import XMonad.Util.PositionStore
 import qualified XMonad.StackSet as S
 import XMonad.Layout.WindowArranger
-import Control.Monad(when)
-import Data.Maybe(isJust)
-import Data.List(nub)
+import XMonad.Prelude (isJust, nub, when)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/Reflect.hs b/XMonad/Layout/Reflect.hs
index 19f6200a..7b52b336 100644
--- a/XMonad/Layout/Reflect.hs
+++ b/XMonad/Layout/Reflect.hs
@@ -24,12 +24,12 @@ module XMonad.Layout.Reflect (
                              ) where
 
 import XMonad.Core
+import XMonad.Prelude (fi)
 import Graphics.X11 (Rectangle(..), Window)
 import Control.Arrow (second)
 
 import XMonad.Layout.LayoutModifier
 import XMonad.Layout.MultiToggle
-import XMonad.Util.XUtils (fi)
 
 -- $usage
 -- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
diff --git a/XMonad/Layout/ResizableThreeColumns.hs b/XMonad/Layout/ResizableThreeColumns.hs
index 7e6e6f4f..04bc879e 100644
--- a/XMonad/Layout/ResizableThreeColumns.hs
+++ b/XMonad/Layout/ResizableThreeColumns.hs
@@ -22,15 +22,13 @@ module XMonad.Layout.ResizableThreeColumns (
                              ) where
 
 import XMonad hiding (splitVertically)
+import XMonad.Prelude
 import XMonad.Layout.ResizableTile(MirrorResize(..))
 import qualified XMonad.StackSet as W
 
-import Data.List ((\\))
 import qualified Data.Map as M
 import Data.Ratio
 
-import Control.Monad
-
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
 --
diff --git a/XMonad/Layout/ResizableTile.hs b/XMonad/Layout/ResizableTile.hs
index 0daf5a89..c9450e1e 100644
--- a/XMonad/Layout/ResizableTile.hs
+++ b/XMonad/Layout/ResizableTile.hs
@@ -21,10 +21,9 @@ module XMonad.Layout.ResizableTile (
                                    ) where
 
 import XMonad hiding (tile, splitVertically, splitHorizontallyBy)
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
-import Control.Monad
 import qualified Data.Map as M
-import Data.List ((\\))
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/SimplestFloat.hs b/XMonad/Layout/SimplestFloat.hs
index 8e983422..3eb01be7 100644
--- a/XMonad/Layout/SimplestFloat.hs
+++ b/XMonad/Layout/SimplestFloat.hs
@@ -19,11 +19,11 @@ module XMonad.Layout.SimplestFloat
     , SimplestFloat
     ) where
 
+import XMonad.Prelude (fi)
 import XMonad
 import qualified XMonad.StackSet as S
 import XMonad.Layout.WindowArranger
 import XMonad.Layout.LayoutModifier
-import XMonad.Util.XUtils (fi)
 
 -- $usage
 -- You can use this module with the following in your
diff --git a/XMonad/Layout/SortedLayout.hs b/XMonad/Layout/SortedLayout.hs
index f57839b7..6d7bd51d 100644
--- a/XMonad/Layout/SortedLayout.hs
+++ b/XMonad/Layout/SortedLayout.hs
@@ -24,10 +24,8 @@ module XMonad.Layout.SortedLayout
   , Property(..)
   ) where
 
-import           Control.Monad
-import           Data.List
-
 import           XMonad
+import           XMonad.Prelude hiding (Const)
 import           XMonad.Layout.LayoutModifier
 import           XMonad.StackSet              as W
 import           XMonad.Util.WindowProperties
diff --git a/XMonad/Layout/StackTile.hs b/XMonad/Layout/StackTile.hs
index 518f855c..8f3fbeac 100644
--- a/XMonad/Layout/StackTile.hs
+++ b/XMonad/Layout/StackTile.hs
@@ -23,7 +23,7 @@ module XMonad.Layout.StackTile (
 
 import XMonad hiding (tile)
 import qualified XMonad.StackSet as W
-import Control.Monad
+import XMonad.Prelude
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/StateFull.hs b/XMonad/Layout/StateFull.hs
index 87d2d817..90d3c043 100644
--- a/XMonad/Layout/StateFull.hs
+++ b/XMonad/Layout/StateFull.hs
@@ -30,12 +30,10 @@ module XMonad.Layout.StateFull (
 ) where
 
 import XMonad hiding ((<&&>))
+import XMonad.Prelude (fromMaybe, (<|>))
 import qualified XMonad.StackSet as W
 import XMonad.Util.Stack (findZ)
 
-import Data.Maybe (fromMaybe)
-import Control.Applicative ((<|>))
-
 -- $Usage
 --
 -- To use it, first you need to:
diff --git a/XMonad/Layout/Stoppable.hs b/XMonad/Layout/Stoppable.hs
index 617b92ae..f32bb1ac 100644
--- a/XMonad/Layout/Stoppable.hs
+++ b/XMonad/Layout/Stoppable.hs
@@ -47,6 +47,7 @@ module XMonad.Layout.Stoppable
     ) where
 
 import XMonad
+import XMonad.Prelude
 import XMonad.Actions.WithAll
 import XMonad.Util.WindowProperties
 import XMonad.Util.RemoteWindows
@@ -54,8 +55,6 @@ import XMonad.Util.Timer
 import XMonad.StackSet hiding (filter)
 import XMonad.Layout.LayoutModifier
 import System.Posix.Signals
-import Data.Maybe
-import Control.Monad
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Layout/SubLayouts.hs b/XMonad/Layout/SubLayouts.hs
index 345e72aa..6545f379 100644
--- a/XMonad/Layout/SubLayouts.hs
+++ b/XMonad/Layout/SubLayouts.hs
@@ -51,11 +51,8 @@ import XMonad.Layout.WindowNavigation(Navigate(Apply))
 import XMonad.Util.Invisible(Invisible(..))
 import XMonad.Util.Types(Direction2D(..))
 import XMonad hiding (def)
+import XMonad.Prelude
 import Control.Arrow(Arrow(second, (&&&)))
-import Control.Monad((<=<), MonadPlus(mplus), foldM, guard, when, join)
-import Data.Function(on)
-import Data.List(nubBy)
-import Data.Maybe(isNothing, fromMaybe, listToMaybe, mapMaybe)
 
 import qualified XMonad as X
 import qualified XMonad.Layout.BoringWindows as B
diff --git a/XMonad/Layout/TabBarDecoration.hs b/XMonad/Layout/TabBarDecoration.hs
index 010c53ee..df549e9a 100644
--- a/XMonad/Layout/TabBarDecoration.hs
+++ b/XMonad/Layout/TabBarDecoration.hs
@@ -21,7 +21,7 @@ module XMonad.Layout.TabBarDecoration
     , module XMonad.Layout.ResizeScreen
     ) where
 
-import Data.List
+import XMonad.Prelude
 import XMonad
 import qualified XMonad.StackSet as S
 import XMonad.Layout.Decoration
diff --git a/XMonad/Layout/Tabbed.hs b/XMonad/Layout/Tabbed.hs
index 7326bd8f..d9745506 100644
--- a/XMonad/Layout/Tabbed.hs
+++ b/XMonad/Layout/Tabbed.hs
@@ -33,7 +33,7 @@ module XMonad.Layout.Tabbed
     , TabbarShown, Direction2D(..)
     ) where
 
-import Data.List
+import XMonad.Prelude
 
 import XMonad
 import qualified XMonad.StackSet as S
diff --git a/XMonad/Layout/TallMastersCombo.hs b/XMonad/Layout/TallMastersCombo.hs
index 7f8702ee..0ccd5a3e 100644
--- a/XMonad/Layout/TallMastersCombo.hs
+++ b/XMonad/Layout/TallMastersCombo.hs
@@ -1,9 +1,9 @@
 -- {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, DeriveDataTypeable, TypeSynonymInstances, MultiParamTypeClasses #-}
 {-# LANGUAGE PatternGuards,
-    FlexibleContexts, 
-    FlexibleInstances, 
-    DeriveDataTypeable, 
-    TypeSynonymInstances, 
+    FlexibleContexts,
+    FlexibleInstances,
+    DeriveDataTypeable,
+    TypeSynonymInstances,
     MultiParamTypeClasses
 #-}
 ---------------------------------------------------------------------------
@@ -16,11 +16,11 @@
 -- Stability   :  unstable
 -- Portability :  unportable
 --
--- A layout combinator that support Shrink, Expand, and IncMasterN just as the 
--- 'Tall' layout, and also support operations of two master windows: 
+-- A layout combinator that support Shrink, Expand, and IncMasterN just as the
+-- 'Tall' layout, and also support operations of two master windows:
 -- a main master, which is the original master window;
 -- a sub master, the first window of the second pane.
--- This combinator can be nested, and has a good support for using 
+-- This combinator can be nested, and has a good support for using
 -- 'XMonad.Layout.Tabbed' as a sublayout.
 --
 -----------------------------------------------------------------------------
@@ -47,11 +47,9 @@ module XMonad.Layout.TallMastersCombo (
 ) where
 
 import XMonad hiding (focus, (|||))
+import XMonad.Prelude (delete, find, foldM, isJust)
 import XMonad.StackSet (Workspace(..),integrate',Stack(..))
 import qualified XMonad.StackSet as W
-import Data.Maybe (isJust)
-import Data.List (delete,find)
-import Control.Monad (foldM)
 import qualified XMonad.Layout as LL
 import XMonad.Layout.Simplest (Simplest(..))
 import XMonad.Layout.Decoration
@@ -71,7 +69,7 @@ import XMonad.Layout.Decoration
 --
 -- > tmsCombineTwoDefault (Tall 0 (3/100) 0) simpleTabbed
 --
--- This will make the 'Tall' layout as the master pane, and 'simpleTabbed' layout as the second pane. 
+-- This will make the 'Tall' layout as the master pane, and 'simpleTabbed' layout as the second pane.
 -- You can shrink, expand, and increase more windows to the master pane just like using the
 -- 'Tall' layout.
 --
@@ -81,7 +79,7 @@ import XMonad.Layout.Decoration
 -- >      , ((modm .|. shiftMask, m),         sendMessage $ FocusSubMaster)
 -- >      , ((modm .|. shiftMask, xK_Return), sendMessage $ SwapSubMaster)
 --
--- In each pane, you can use multiple layouts with the '(|||)' combinator provided by this module, 
+-- In each pane, you can use multiple layouts with the '(|||)' combinator provided by this module,
 -- and switch between them with the 'FocusedNextLayout' message. Below is one example
 --
 -- > layout1 = Simplest ||| Tabbed
@@ -91,14 +89,14 @@ import XMonad.Layout.Decoration
 -- then add the following key binding,
 --
 -- >      , ((modm, w), sendMessage $ FocusedNextLayout)
--- 
+--
 -- Now, pressing this key will toggle the multiple layouts in the currently focused pane.
 --
 -- You can mirror this layout with the default 'Mirror' key binding. But to have a more natural
 -- behaviors, you can use the 'SwitchOrientation' message:
 --
 -- >      , ((modm, xK_space), sendMessage $ SwitchOrientation)
--- 
+--
 -- This will not mirror the tabbed decoration, and will keep sub-layouts that made by TallMastersCombo
 -- and RowsOrColumns display in natural orientations.
 --
@@ -106,7 +104,7 @@ import XMonad.Layout.Decoration
 --
 -- > tmsCombineTwo False 1 (3/100) (1/3) Simplest simpleTabbed
 --
--- This creates a vertical merged layout with 1 window in the master pane, and the master pane shrinks 
+-- This creates a vertical merged layout with 1 window in the master pane, and the master pane shrinks
 -- and expands with a step of (3\/100), and occupies (1\/3) of the screen.
 --
 -- Each sub-layout have a focused window. To rotate between the focused windows across all the
@@ -145,7 +143,7 @@ data RowsOrColumns a = RowsOrColumns { rowMode :: Bool -- ^ arrange windows in r
                                      } deriving (Show, Read)
 
 instance LayoutClass RowsOrColumns a where
-  description (RowsOrColumns rows) = 
+  description (RowsOrColumns rows) =
     if rows then "Rows" else "Columns"
 
   pureLayout (RowsOrColumns rows) r s = zip ws rs
@@ -154,14 +152,14 @@ instance LayoutClass RowsOrColumns a where
           rs = if rows
                then splitVertically len r
                else splitHorizontally len r
-    
+
   pureMessage (RowsOrColumns rows) m
     | Just Row <- fromMessage m = Just $ RowsOrColumns True
     | Just Col <- fromMessage m = Just $ RowsOrColumns False
     | otherwise = Nothing
 
 
-data TMSCombineTwo l1 l2 a = 
+data TMSCombineTwo l1 l2 a =
   TMSCombineTwo { focusLst :: [a]
                 , ws1 :: [a]
                 , ws2 :: [a]
@@ -175,14 +173,14 @@ data TMSCombineTwo l1 l2 a =
         deriving (Show, Read)
 
 -- | Combine two layouts l1 l2 with default behaviors.
-tmsCombineTwoDefault :: (LayoutClass l1 Window, LayoutClass l2 Window) => 
+tmsCombineTwoDefault :: (LayoutClass l1 Window, LayoutClass l2 Window) =>
                           l1 Window -> l2 Window -> TMSCombineTwo l1 l2 Window
 tmsCombineTwoDefault = TMSCombineTwo [] [] [] True 1 (3/100) (1/2)
 
 -- | A more flexible way of merging two layouts. User can specify if merge them vertical or horizontal,
 -- the number of windows in the first pane (master pane), the shink and expand increment, and the proportion
 -- occupied by the master pane.
-tmsCombineTwo :: (LayoutClass l1 Window, LayoutClass l2 Window) => 
+tmsCombineTwo :: (LayoutClass l1 Window, LayoutClass l2 Window) =>
                   Bool -> Int -> Rational -> Rational -> l1 Window -> l2 Window -> TMSCombineTwo l1 l2 Window
 tmsCombineTwo = TMSCombineTwo [] [] []
 
@@ -190,9 +188,9 @@ data Orientation = Row | Col deriving (Read, Show, Typeable)
 instance Message Orientation
 
 -- | A message that switches the orientation of TallMasterCombo layout and the RowsOrColumns layout.
--- This is similar to the 'Mirror' message, but 'Mirror' cannot apply to hidden layouts, and when 'Mirror' 
--- applies to the 'XMonad.Layout.Tabbed' decoration, it will also mirror the tabs, which may lead to unintended 
--- visualizations. The 'SwitchOrientation' message refreshes layouts according to the orientation of the parent layout, 
+-- This is similar to the 'Mirror' message, but 'Mirror' cannot apply to hidden layouts, and when 'Mirror'
+-- applies to the 'XMonad.Layout.Tabbed' decoration, it will also mirror the tabs, which may lead to unintended
+-- visualizations. The 'SwitchOrientation' message refreshes layouts according to the orientation of the parent layout,
 -- and will not affect the 'XMonad.Layout.Tabbed' decoration.
 data SwitchOrientation = SwitchOrientation deriving (Read, Show, Typeable)
 instance Message SwitchOrientation
@@ -217,13 +215,13 @@ instance Message ChangeFocus
 instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombineTwo l1 l2) Window where
   description _ = "TallMasters"
 
-  runLayout (Workspace wid l@(TMSCombineTwo f w1 w2 vsp nmaster delta frac layout1 layout2) s) r = 
+  runLayout (Workspace wid l@(TMSCombineTwo f w1 w2 vsp nmaster delta frac layout1 layout2) s) r =
       let (s1,s2,frac',slst1,slst2) = splitStack f nmaster frac s
           (r1, r2) = if vsp
                      then splitHorizontallyBy frac' r
                      else splitVerticallyBy frac' r
-      in 
-      do 
+      in
+      do
          (ws1,ml1) <- runLayout (Workspace wid layout1 s1) r1
          (ws2,ml2) <- runLayout (Workspace wid layout2 s2) r2
          let newlayout1 = maybe layout1 id ml1
@@ -238,18 +236,18 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
     -- messages that only traverse one level
     | Just Shrink <- fromMessage m = return . Just $ TMSCombineTwo f w1 w2 vsp nmaster delta (max 0 $ frac-delta) layout1 layout2
     | Just Expand <- fromMessage m = return . Just $ TMSCombineTwo f w1 w2 vsp nmaster delta (min 1 $ frac+delta) layout1 layout2
-    | Just (IncMasterN d) <- fromMessage m = 
+    | Just (IncMasterN d) <- fromMessage m =
         let w = w1++w2
             nmasterNew = min (max 0 (nmaster+d)) (length w)
             (w1',w2')  = splitAt nmasterNew w
         in return . Just $ TMSCombineTwo f w1' w2' vsp nmasterNew delta frac layout1 layout2
-    | Just SwitchOrientation <- fromMessage m = 
+    | Just SwitchOrientation <- fromMessage m =
             let m1 = if vsp then SomeMessage Col else SomeMessage Row
             in
             do mlayout1 <- handleMessage layout1 m1
                mlayout2 <- handleMessage layout2 m1
                return $ mergeSubLayouts  mlayout1 mlayout2 (TMSCombineTwo f w1 w2 (not vsp) nmaster delta frac layout1 layout2) True
-    | Just SwapSubMaster <- fromMessage m = 
+    | Just SwapSubMaster <- fromMessage m =
         -- first get the submaster window
         let subMaster = if null w2 then Nothing else Just $ head w2
         in case subMaster of
@@ -266,7 +264,7 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
     | Just NextFocus <- fromMessage m =
         do
           -- All toggle message is passed to the sublayout with focused window
-          mst <- gets (W.stack . W.workspace . W.current . windowset) 
+          mst <- gets (W.stack . W.workspace . W.current . windowset)
           let nextw = adjFocus f mst True
           case nextw of Nothing -> return Nothing
                         Just w  -> do windows $ W.modify' $ focusWindow w
@@ -274,7 +272,7 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
     | Just PrevFocus <- fromMessage m =
         do
           -- All toggle message is passed to the sublayout with focused window
-          mst <- gets (W.stack . W.workspace . W.current . windowset) 
+          mst <- gets (W.stack . W.workspace . W.current . windowset)
           let prevw = adjFocus f mst False
           case prevw of Nothing -> return Nothing
                         Just w  -> do windows $ W.modify' $ focusWindow w
@@ -288,14 +286,14 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
         do mlayout1 <- handleMessage layout1 (SomeMessage Row)
            mlayout2 <- handleMessage layout2 (SomeMessage Row)
            return $ mergeSubLayouts mlayout1 mlayout2 (TMSCombineTwo f w1 w2 True nmaster delta frac layout1 layout2) True
-    | Just FocusedNextLayout <- fromMessage m = 
+    | Just FocusedNextLayout <- fromMessage m =
        do
        -- All toggle message is passed to the sublayout with focused window
-         mst <- gets (W.stack . W.workspace . W.current . windowset) 
+         mst <- gets (W.stack . W.workspace . W.current . windowset)
          let focId = findFocused mst w1 w2
              m1 = if vsp then SomeMessage Row else SomeMessage Col
          if focId == 1
-           then do 
+           then do
                  mlay1 <- handleMessages layout1 [(SomeMessage NextLayout), m1]
                  let mlay2 = Nothing
                  return $ mergeSubLayouts mlay1 mlay2 i True
@@ -303,7 +301,7 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
                  let mlay1 = Nothing
                  mlay2 <- handleMessages layout2 [(SomeMessage NextLayout), m1]
                  return $ mergeSubLayouts mlay1 mlay2 i True
-    | otherwise = 
+    | otherwise =
             do
               mlayout1 <- handleMessage layout1 m
               mlayout2 <- handleMessage layout2 m
@@ -324,7 +322,7 @@ differentiate [] xs = W.differentiate xs
 
 -- | Swap a given window with the focused window.
 swapWindow :: (Eq a) => a -> Stack a -> Stack a
-swapWindow w s = 
+swapWindow w s =
   let upLst   = up s
       foc     = focus s
       downLst = down s
@@ -341,12 +339,12 @@ swapWindow w s =
 
 -- | Focus a given window.
 focusWindow :: (Eq a) => a -> Stack a -> Stack a
-focusWindow w s = 
-  if elem w (up s) 
+focusWindow w s =
+  if elem w (up s)
   then focusSubMasterU w s
   else focusSubMasterD w s
   where
-      focusSubMasterU w i@(Stack foc (l:ls) rs) = 
+      focusSubMasterU w i@(Stack foc (l:ls) rs) =
           if foc == w
           then i
           else
@@ -354,7 +352,7 @@ focusWindow w s =
               then news
               else focusSubMasterU w news
               where news = Stack l ls (foc:rs)
-      focusSubMasterU w (Stack foc [] rs) = 
+      focusSubMasterU w (Stack foc [] rs) =
           Stack foc [] rs
       focusSubMasterD w i@(Stack foc ls (r:rs)) =
           if foc == w
@@ -364,7 +362,7 @@ focusWindow w s =
               then news
               else focusSubMasterD w news
               where news = Stack r (foc:ls) rs
-      focusSubMasterD w (Stack foc ls []) = 
+      focusSubMasterD w (Stack foc ls []) =
           Stack foc ls []
 
 -- | Merge two Maybe sublayouts.
@@ -392,7 +390,7 @@ handleMessages :: (LayoutClass l a) => l a -> [SomeMessage] -> X (Maybe (l a))
 handleMessages l ms = foldM  handleMaybeMsg (Just l) ms
 
 handleMaybeMsg :: (LayoutClass l a) => Maybe (l a) -> SomeMessage -> X (Maybe (l a))
-handleMaybeMsg ml m = case ml of Just l  -> do 
+handleMaybeMsg ml m = case ml of Just l  -> do
                                               res <- handleMessage l m
                                               return $ elseOr (Just l) res
                                  Nothing -> return Nothing
@@ -418,7 +416,7 @@ type Next = Bool
 adjFocus :: (Eq a) => [a] -> Maybe (Stack a) -> Next -> Maybe a
 adjFocus ws ms next =
   case ms of Nothing -> Nothing
-             Just s  -> let searchLst = 
+             Just s  -> let searchLst =
                               case next of True  -> (down s) ++ (reverse (up s))
                                            False -> (up s) ++ (reverse (down s))
                         in  find (flip elem ws) searchLst
@@ -445,16 +443,16 @@ handle l m = handleMessage l (SomeMessage m)
 instance (GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a where
   description (ChooseWrapper d l r lr) = description lr
 
-  runLayout (Workspace wid (ChooseWrapper d l r lr) s) rec = 
-    do 
+  runLayout (Workspace wid (ChooseWrapper d l r lr) s) rec =
+    do
       let (l', r') = case d of L -> (savFocused l s, r)
                                R -> (l, savFocused r s)
       (ws, ml0) <- runLayout (Workspace wid lr s) rec
       let l1 = case ml0 of Just l0 -> Just $ ChooseWrapper d l' r' l0
                            Nothing -> Nothing
       return $ (ws,l1)
-    
-  handleMessage c@(ChooseWrapper d l r lr) m 
+
+  handleMessage c@(ChooseWrapper d l r lr) m
     | Just NextLayout <- fromMessage m = do
         mlr' <- handleMessage lr m
         mlrf <- handle c NextNoWrap
@@ -466,11 +464,11 @@ instance (GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a w
                      Nothing  -> return Nothing
     | Just NextNoWrap <- fromMessage m = do
         mlr' <- handleMessage lr m
-        (d',l',r', end) <- 
-              case d of 
+        (d',l',r', end) <-
+              case d of
                 L -> do
                        ml <- handle l NextNoWrap
-                       case ml of 
+                       case ml of
                            Just l0 -> return (L,l0,r,0)
                            Nothing -> do
                                   mr <- handle r FirstLayout
@@ -483,7 +481,7 @@ instance (GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a w
                          Just r0 -> return (R,l,r0,0)
                          Nothing -> return (d,l,r,1)
         case mlr' of Just lrt -> return $ Just $ ChooseWrapper d' l' r' lrt
-                     Nothing  -> 
+                     Nothing  ->
                         case end of 0 -> return $ Just $ ChooseWrapper d' l' r' lr
                                     1 -> return Nothing
     | Just FirstLayout <- fromMessage m = do
@@ -520,14 +518,14 @@ instance (GetFocused l Window, GetFocused r Window) => GetFocused (TMSCombineTwo
         (f2, str2) = getFocused lay2 s2
     in  (f1 ++ f2, "TMS: " ++ show f ++ "::" ++ str1 ++ "--" ++ str2)
   savFocused i@(TMSCombineTwo f _ _ _ nmaster _ frac lay1 lay2) s =
-    let (s1,s2,_,_,_) = splitStack f nmaster frac s 
+    let (s1,s2,_,_,_) = splitStack f nmaster frac s
         (f', mstr) = getFocused i s
         lay1' = savFocused lay1 s1
         lay2' = savFocused lay2 s2
     in i {focusLst = f', layoutFst=lay1', layoutSnd=lay2'}
-  
+
 instance (GetFocused l a, GetFocused r a) => GetFocused (ChooseWrapper l r) a where
-  getFocused (ChooseWrapper d l r _) s = 
+  getFocused (ChooseWrapper d l r _) s =
     case d of L -> getFocused l s
               R -> getFocused r s
   savFocused (ChooseWrapper d l r lr) s =
@@ -541,4 +539,3 @@ instance (Typeable a) => GetFocused RowsOrColumns a
 instance (Typeable a) => GetFocused Full a
 instance (Typeable a) => GetFocused Tall a
 instance (Typeable l, Typeable a, Typeable m, LayoutModifier m a, LayoutClass l a) => GetFocused (ModifiedLayout m l) a
-
diff --git a/XMonad/Layout/ThreeColumns.hs b/XMonad/Layout/ThreeColumns.hs
index 458f37a0..9b701e16 100644
--- a/XMonad/Layout/ThreeColumns.hs
+++ b/XMonad/Layout/ThreeColumns.hs
@@ -25,12 +25,11 @@ module XMonad.Layout.ThreeColumns (
                              ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as W
 
 import Data.Ratio
 
-import Control.Monad
-
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
 --
diff --git a/XMonad/Layout/TrackFloating.hs b/XMonad/Layout/TrackFloating.hs
index 8d682e0e..660933fe 100644
--- a/XMonad/Layout/TrackFloating.hs
+++ b/XMonad/Layout/TrackFloating.hs
@@ -33,9 +33,7 @@ module XMonad.Layout.TrackFloating
      UseTransientFor,
     ) where
 
-import Control.Applicative ((<|>))
-import Control.Monad
-
+import XMonad.Prelude
 import XMonad
 import XMonad.Layout.LayoutModifier
 import XMonad.Util.Stack (findZ)
diff --git a/XMonad/Layout/WindowArranger.hs b/XMonad/Layout/WindowArranger.hs
index 1c2a270b..9cbcdf89 100644
--- a/XMonad/Layout/WindowArranger.hs
+++ b/XMonad/Layout/WindowArranger.hs
@@ -26,12 +26,11 @@ module XMonad.Layout.WindowArranger
     ) where
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.StackSet as S
 import XMonad.Layout.LayoutModifier
-import XMonad.Util.XUtils (fi)
 
-import Control.Arrow
-import Data.List
+import Control.Arrow ((***), (>>>), (&&&), first)
 
 -- $usage
 -- You can use this module with the following in your
diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index 462da30a..fd1523c4 100644
--- a/XMonad/Layout/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -25,7 +25,7 @@ module XMonad.Layout.WindowNavigation (
                                    WindowNavigation,
                                   ) where
 
-import Data.List ( nub, sortBy, (\\) )
+import XMonad.Prelude ( nub, sortBy, (\\) )
 import XMonad hiding (Point)
 import qualified XMonad.StackSet as W
 import XMonad.Layout.LayoutModifier
diff --git a/XMonad/Layout/WindowSwitcherDecoration.hs b/XMonad/Layout/WindowSwitcherDecoration.hs
index 4a93c014..8bd01c5f 100644
--- a/XMonad/Layout/WindowSwitcherDecoration.hs
+++ b/XMonad/Layout/WindowSwitcherDecoration.hs
@@ -30,7 +30,7 @@ import XMonad.Layout.DecorationAddons
 import XMonad.Layout.ImageButtonDecoration
 import XMonad.Layout.DraggingVisualizer
 import qualified XMonad.StackSet as S
-import Control.Monad
+import XMonad.Prelude
 import Foreign.C.Types(CInt)
 
 -- $usage
diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs
index b02f26ab..aa880326 100644
--- a/XMonad/Layout/WorkspaceDir.hs
+++ b/XMonad/Layout/WorkspaceDir.hs
@@ -31,7 +31,7 @@ module XMonad.Layout.WorkspaceDir (
                                   ) where
 
 import System.Directory ( setCurrentDirectory, getCurrentDirectory )
-import Control.Monad ( when )
+import XMonad.Prelude ( when )
 
 import XMonad hiding ( focus )
 import XMonad.Prompt ( XPConfig )
diff --git a/XMonad/Layout/ZoomRow.hs b/XMonad/Layout/ZoomRow.hs
index 816e64c0..a26f02b6 100644
--- a/XMonad/Layout/ZoomRow.hs
+++ b/XMonad/Layout/ZoomRow.hs
@@ -35,12 +35,11 @@ module XMonad.Layout.ZoomRow ( -- * Usage
                              ) where
 
 import XMonad
+import XMonad.Prelude (fromMaybe, fi)
 import qualified XMonad.StackSet as W
 
 import XMonad.Util.Stack
-import XMonad.Layout.Decoration (fi)
 
-import Data.Maybe (fromMaybe)
 import Control.Arrow (second)
 
 -- $usage
@@ -255,4 +254,4 @@ instance (EQF f a, Show a, Read a, Show (f a), Read (f a), Typeable f)
                                      $ SomeMessage $ ZoomFull $ not b
             _ -> Nothing
 
-    pureMessage _ _ = Nothing
\ No newline at end of file
+    pureMessage _ _ = Nothing
diff --git a/XMonad/Prelude.hs b/XMonad/Prelude.hs
new file mode 100644
index 00000000..b87fde66
--- /dev/null
+++ b/XMonad/Prelude.hs
@@ -0,0 +1,55 @@
+{-# LANGUAGE BangPatterns #-}
+--------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Prelude
+-- Copyright   :  slotThe <soliditsallgood@mailbox.org>
+-- License     :  BSD3-style (see LICENSE)
+--
+-- Maintainer  :  slotThe <soliditsallgood@mailbox.org>
+--
+-- Utility functions and re-exports for a more ergonomic developing
+-- experience.  Users themselves will not find much use here.
+--
+--------------------------------------------------------------------
+module XMonad.Prelude (
+    module Exports,
+    fi,
+    chunksOf,
+    (.:),
+    (!?),
+) where
+
+import Control.Applicative as Exports
+import Control.Monad       as Exports
+import Data.Bool           as Exports
+import Data.Char           as Exports
+import Data.Foldable       as Exports
+import Data.Function       as Exports
+import Data.Functor        as Exports
+import Data.List           as Exports
+import Data.Maybe          as Exports
+import Data.Monoid         as Exports
+import Data.Traversable    as Exports
+
+-- | Short for 'fromIntegral'.
+fi :: (Integral a, Num b) => a -> b
+fi = fromIntegral
+
+-- | Given a maximum length, splits a list into sublists
+--
+-- >>> chunksOf 5 (take 30 $ repeat 'a')
+-- ["aaaaa","aaaaa","aaaaa","aaaaa","aaaaa","aaaaa"]
+chunksOf :: Int -> [a] -> [[a]]
+chunksOf _ [] = []
+chunksOf i xs = chunk : chunksOf i rest
+  where !(chunk, rest) = splitAt i xs
+
+-- | Safe version of '(!!)'.
+(!?) :: [a] -> Int -> Maybe a
+(!?) xs n = listToMaybe $ drop n xs
+
+-- | Multivariant composition.
+--
+-- > f .: g ≡ (f .) . g ≡ \c d -> f (g c d)
+(.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b
+(.:) = (.) . (.)
diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs
index fa65690a..c3886d8c 100644
--- a/XMonad/Prompt.hs
+++ b/XMonad/Prompt.hs
@@ -94,6 +94,7 @@ module XMonad.Prompt
     ) where
 
 import           XMonad                       hiding (cleanMask, config)
+import           XMonad.Prelude               hiding (toList)
 import qualified XMonad                       as X (numberlockMask)
 import qualified XMonad.StackSet              as W
 import           XMonad.Util.Font
@@ -107,11 +108,8 @@ import           Control.Exception            as E hiding (handle)
 import           Control.Monad.State
 import           Data.Bifunctor               (bimap)
 import           Data.Bits
-import           Data.Char                    (isSpace)
 import           Data.IORef
-import           Data.List
 import qualified Data.Map                     as M
-import           Data.Maybe                   (fromMaybe, listToMaybe)
 import           Data.Set                     (fromList, toList)
 import           System.IO
 import           System.IO.Unsafe             (unsafePerformIO)
@@ -413,15 +411,11 @@ highlightedItem st' completions = case complWinDim st' of
   Just winDim ->
     let
       (_,_,_,_,xx,yy) = winDim
-      complMatrix = splitInSubListsAt (length yy) (take (length xx * length yy) completions)
+      complMatrix = chunksOf (length yy) (take (length xx * length yy) completions)
       (col_index,row_index) = complIndex st'
     in case completions of
       [] -> Nothing
       _  -> complMatrix !? col_index >>= (!? row_index)
- where
-  -- | Safe version of '(!!)'.
-  (!?) :: [a] -> Int -> Maybe a
-  (!?) xs n = listToMaybe $ drop n xs
 
 -- | Return the selected completion, i.e. the 'String' we actually act
 -- upon after the user confirmed their selection (by pressing @Enter@).
@@ -1561,7 +1555,7 @@ drawComplWin w compl = do
   p <- io $ createPixmap d w wh ht
                          (defaultDepthOfScreen scr)
   io $ fillDrawable d p gc borderC bgcolor (fi bw) wh ht
-  let ac = splitInSubListsAt (length yy) (take (length xx * length yy) compl)
+  let ac = chunksOf (length yy) (take (length xx * length yy) compl)
 
   printComplList d p gc (fgNormal cr) (bgNormal cr) xx yy ac
   --lift $ spawn $ "xmessage " ++ " ac: " ++ show ac  ++ " xx: " ++ show xx ++ " length xx: " ++ show (length xx) ++ " yy: " ++ show (length yy)
@@ -1704,9 +1698,8 @@ getNextCompletion c l = l !! idx
 
 -- | Given a maximum length, splits a list into sublists
 splitInSubListsAt :: Int -> [a] -> [[a]]
-splitInSubListsAt _ [] = []
-splitInSubListsAt i x = f : splitInSubListsAt i rest
-    where (f,rest) = splitAt i x
+splitInSubListsAt = chunksOf
+{-# DEPRECATED splitInSubListsAt "Use XMonad.Prelude.chunksOf instead." #-}
 
 -- | Gets the last word of a string or the whole string if formed by
 -- only one word
diff --git a/XMonad/Prompt/DirExec.hs b/XMonad/Prompt/DirExec.hs
index 9f415198..804c2d61 100644
--- a/XMonad/Prompt/DirExec.hs
+++ b/XMonad/Prompt/DirExec.hs
@@ -26,10 +26,8 @@ module XMonad.Prompt.DirExec
 
 import Control.Exception as E
 import System.Directory
-import Control.Applicative (liftA2)
-import Control.Monad
-import Data.List
 import XMonad
+import XMonad.Prelude
 import XMonad.Prompt
 
 econst :: Monad m => a -> IOException -> m a
diff --git a/XMonad/Prompt/Directory.hs b/XMonad/Prompt/Directory.hs
index 5488e31c..9b16c8db 100644
--- a/XMonad/Prompt/Directory.hs
+++ b/XMonad/Prompt/Directory.hs
@@ -21,7 +21,7 @@ module XMonad.Prompt.Directory (
                              Dir
                               ) where
 
-import Data.List ( sort )
+import XMonad.Prelude ( sort )
 
 import XMonad
 import XMonad.Prompt
diff --git a/XMonad/Prompt/FuzzyMatch.hs b/XMonad/Prompt/FuzzyMatch.hs
index 2e3772c6..40250075 100644
--- a/XMonad/Prompt/FuzzyMatch.hs
+++ b/XMonad/Prompt/FuzzyMatch.hs
@@ -18,9 +18,7 @@ module XMonad.Prompt.FuzzyMatch ( -- * Usage
                                 , fuzzySort
                                 ) where
 
-import Data.Char
-import Data.Function
-import Data.List
+import XMonad.Prelude
 
 -- $usage
 --
diff --git a/XMonad/Prompt/Layout.hs b/XMonad/Prompt/Layout.hs
index 51efad24..f419830a 100644
--- a/XMonad/Prompt/Layout.hs
+++ b/XMonad/Prompt/Layout.hs
@@ -18,7 +18,7 @@ module XMonad.Prompt.Layout (
                              layoutPrompt
                             ) where
 
-import Data.List ( sort, nub )
+import XMonad.Prelude ( sort, nub )
 import XMonad hiding ( workspaces )
 import XMonad.Prompt
 import XMonad.Prompt.Workspace ( Wor(..) )
diff --git a/XMonad/Prompt/Man.hs b/XMonad/Prompt/Man.hs
index cc324ac9..a9a15de9 100644
--- a/XMonad/Prompt/Man.hs
+++ b/XMonad/Prompt/Man.hs
@@ -25,6 +25,7 @@ module XMonad.Prompt.Man (
 
 
 import XMonad
+import XMonad.Prelude
 import XMonad.Prompt
 import XMonad.Util.Run
 import XMonad.Prompt.Shell (split)
@@ -34,9 +35,6 @@ import System.Process
 import System.IO
 
 import qualified Control.Exception as E
-import Control.Monad
-import Data.List
-import Data.Maybe
 
 -- $usage
 -- 1. In your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Prompt/OrgMode.hs b/XMonad/Prompt/OrgMode.hs
index 16f9225b..e218815e 100644
--- a/XMonad/Prompt/OrgMode.hs
+++ b/XMonad/Prompt/OrgMode.hs
@@ -37,16 +37,12 @@ module XMonad.Prompt.OrgMode (
     OrgMode,                -- abstract
 ) where
 
+import XMonad.Prelude
+
 import XMonad (X, io)
 import XMonad.Prompt (XPConfig, XPrompt (showXPrompt), mkXPrompt)
 import XMonad.Util.XSelection (getSelection)
 
-import Control.Applicative (empty)
-import Control.Monad ((<=<))
-import Data.Char (isDigit)
-import Data.Functor ((<&>))
-import Data.List (foldl')
-import Data.Maybe (fromMaybe, listToMaybe)
 import Data.Time (Day (ModifiedJulianDay), NominalDiffTime, UTCTime (utctDay), addUTCTime, defaultTimeLocale, formatTime, fromGregorian, getCurrentTime, iso8601DateFormat, nominalDay, toGregorian)
 import System.Directory (getHomeDirectory)
 import System.IO (IOMode (AppendMode), hPutStrLn, withFile)
@@ -382,10 +378,3 @@ pInt = read <$> munch1 isDigit
 -- parsing when the left-most parser succeeds.
 lchoice :: [ReadP a] -> ReadP a
 lchoice = foldl' (<++) empty
-
-------------------------------------------------------------------------
--- Util
-
--- | Multivariant composition.
-(.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b
-(.:) = (.) . (.)
diff --git a/XMonad/Prompt/RunOrRaise.hs b/XMonad/Prompt/RunOrRaise.hs
index 428d50c7..c9e81998 100644
--- a/XMonad/Prompt/RunOrRaise.hs
+++ b/XMonad/Prompt/RunOrRaise.hs
@@ -21,13 +21,13 @@ module XMonad.Prompt.RunOrRaise
     ) where
 
 import XMonad hiding (config)
+import XMonad.Prelude (liftA2)
 import XMonad.Prompt
 import XMonad.Prompt.Shell
 import XMonad.Actions.WindowGo (runOrRaise)
 import XMonad.Util.Run (runProcessWithInput)
 
 import Control.Exception as E
-import Control.Applicative (liftA2)
 import System.Directory (doesDirectoryExist, doesFileExist, executable, getPermissions)
 
 econst :: Monad m => a -> IOException -> m a
diff --git a/XMonad/Prompt/Shell.hs b/XMonad/Prompt/Shell.hs
index 93d105db..1126c145 100644
--- a/XMonad/Prompt/Shell.hs
+++ b/XMonad/Prompt/Shell.hs
@@ -37,15 +37,13 @@ module XMonad.Prompt.Shell
 
 import           Codec.Binary.UTF8.String (encodeString)
 import           Control.Exception        as E
-import           Control.Monad            (forM)
 import           Data.Bifunctor           (bimap)
-import           Data.Char                (toLower)
-import           Data.List                (isInfixOf, isPrefixOf, sortBy)
 import           System.Directory         (getDirectoryContents)
 import           System.Environment       (getEnv)
 import           System.Posix.Files       (getFileStatus, isDirectory)
 
 import           XMonad                   hiding (config)
+import           XMonad.Prelude
 import           XMonad.Prompt
 import           XMonad.Util.Run
 
diff --git a/XMonad/Prompt/Ssh.hs b/XMonad/Prompt/Ssh.hs
index 6add5fd4..15d9ac7f 100644
--- a/XMonad/Prompt/Ssh.hs
+++ b/XMonad/Prompt/Ssh.hs
@@ -20,6 +20,7 @@ module XMonad.Prompt.Ssh
     ) where
 
 import XMonad
+import XMonad.Prelude
 import XMonad.Util.Run
 import XMonad.Prompt
 
@@ -27,10 +28,6 @@ import System.Directory
 import System.Environment
 import Control.Exception as E
 
-import Control.Applicative (liftA2)
-import Data.Maybe
-import Data.List(elemIndex)
-
 econst :: Monad m => a -> IOException -> m a
 econst = const . return
 
diff --git a/XMonad/Prompt/Theme.hs b/XMonad/Prompt/Theme.hs
index 14aa217d..7b0a5e72 100644
--- a/XMonad/Prompt/Theme.hs
+++ b/XMonad/Prompt/Theme.hs
@@ -20,7 +20,7 @@ module XMonad.Prompt.Theme
 
 import Control.Arrow ( (&&&) )
 import qualified Data.Map as M
-import Data.Maybe ( fromMaybe )
+import XMonad.Prelude ( fromMaybe )
 import XMonad
 import XMonad.Prompt
 import XMonad.Layout.Decoration
diff --git a/XMonad/Prompt/Unicode.hs b/XMonad/Prompt/Unicode.hs
index 5a73fe96..32a82bb4 100644
--- a/XMonad/Prompt/Unicode.hs
+++ b/XMonad/Prompt/Unicode.hs
@@ -25,17 +25,15 @@ module XMonad.Prompt.Unicode (
  ) where
 
 import qualified Data.ByteString.Char8 as BS
-import Data.Char
-import Data.Maybe
 import Data.Ord
 import Numeric
 import System.IO
 import System.IO.Error
-import Control.Arrow
-import Data.List
 import Text.Printf
+import Control.Arrow (second)
 
 import XMonad
+import XMonad.Prelude
 import qualified XMonad.Util.ExtensibleState as XS
 import XMonad.Util.Run
 import XMonad.Prompt
diff --git a/XMonad/Prompt/Window.hs b/XMonad/Prompt/Window.hs
index 24367cbc..052068b8 100644
--- a/XMonad/Prompt/Window.hs
+++ b/XMonad/Prompt/Window.hs
@@ -32,7 +32,7 @@ module XMonad.Prompt.Window
     windowPromptBringCopy,
     ) where
 
-import Control.Monad (forM)
+import XMonad.Prelude (forM)
 import qualified Data.Map as M
 
 import qualified XMonad.StackSet as W
diff --git a/XMonad/Prompt/XMonad.hs b/XMonad/Prompt/XMonad.hs
index fce2ef1b..45cfdc67 100644
--- a/XMonad/Prompt/XMonad.hs
+++ b/XMonad/Prompt/XMonad.hs
@@ -23,7 +23,7 @@ module XMonad.Prompt.XMonad (
 import XMonad
 import XMonad.Prompt
 import XMonad.Actions.Commands (defaultCommands)
-import Data.Maybe (fromMaybe)
+import XMonad.Prelude (fromMaybe)
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
diff --git a/XMonad/Util/ClickableWorkspaces.hs b/XMonad/Util/ClickableWorkspaces.hs
index 03773d3a..36e4d459 100644
--- a/XMonad/Util/ClickableWorkspaces.hs
+++ b/XMonad/Util/ClickableWorkspaces.hs
@@ -21,9 +21,7 @@ module XMonad.Util.ClickableWorkspaces (
   clickableWrap,
   ) where
 
-import Control.Monad ((>=>))
-import Data.Functor ((<&>))
-
+import XMonad.Prelude ((<&>), (>=>))
 import XMonad
 import XMonad.Hooks.StatusBar.PP (xmobarAction, PP(..))
 import XMonad.Util.WorkspaceCompare (getSortByIndex)
diff --git a/XMonad/Util/DebugWindow.hs b/XMonad/Util/DebugWindow.hs
index 5620f04c..0356bf95 100644
--- a/XMonad/Util/DebugWindow.hs
+++ b/XMonad/Util/DebugWindow.hs
@@ -8,7 +8,7 @@
 -- Stability   :  unstable
 -- Portability :  not portable
 --
--- Module to dump window information for diagnostic/debugging purposes. See 
+-- Module to dump window information for diagnostic/debugging purposes. See
 -- "XMonad.Hooks.DebugEvents" and "XMonad.Hooks.DebugStack" for practical uses.
 --
 -----------------------------------------------------------------------------
@@ -18,13 +18,10 @@ module XMonad.Util.DebugWindow (debugWindow) where
 import           Prelude
 
 import           XMonad
+import           XMonad.Prelude
 
 import           Codec.Binary.UTF8.String        (decodeString)
 import           Control.Exception                                     as E
-import           Control.Monad                   (when)
-import           Data.List                       (unfoldr
-                                                 ,intercalate
-                                                 )
 import           Foreign
 import           Foreign.C.String
 import           Numeric                         (showHex)
@@ -96,7 +93,7 @@ debugWindow w =  do
                       ,show x
                       ,',':show y
                       ,if null c then "" else ' ':c
-                      ,if null cmd then "" else ' ':cmd 
+                      ,if null cmd then "" else ' ':cmd
                       ,rb
                       ]
 
diff --git a/XMonad/Util/Dzen.hs b/XMonad/Util/Dzen.hs
index 4702ed7f..05a2f4f4 100644
--- a/XMonad/Util/Dzen.hs
+++ b/XMonad/Util/Dzen.hs
@@ -42,7 +42,7 @@ module XMonad.Util.Dzen (
     (>=>),
   ) where
 
-import Control.Monad
+import XMonad.Prelude
 import XMonad
 import XMonad.StackSet
 import XMonad.Util.Run (runProcessWithInputAndWait, seconds)
diff --git a/XMonad/Util/EZConfig.hs b/XMonad/Util/EZConfig.hs
index 227f3489..49e81ca3 100644
--- a/XMonad/Util/EZConfig.hs
+++ b/XMonad/Util/EZConfig.hs
@@ -38,14 +38,13 @@ module XMonad.Util.EZConfig (
 
 import XMonad
 import XMonad.Actions.Submap
+import XMonad.Prelude hiding (many)
 
 import XMonad.Util.NamedActions
 
-import qualified Data.Map as M
-import Data.List (foldl', sortBy, groupBy, nub)
-import Data.Ord (comparing)
-import Data.Maybe
 import Control.Arrow (first, (&&&))
+import qualified Data.Map as M
+import Data.Ord (comparing)
 
 import Text.ParserCombinators.ReadP
 
@@ -382,9 +381,6 @@ mkSubmaps' subm binds = map combine gathered
                       subm . mkSubmaps' subm $ map (first tail) ks)
         fstKey = (==) `on` (head . fst)
 
-on :: (a -> a -> b) -> (c -> a) -> c -> c -> b
-op `on` f = \x y -> f x `op` f y
-
 -- | Given a configuration record and a list of (key sequence
 --   description, action) pairs, parse the key sequences into lists of
 --   @(KeyMask,KeySym)@ pairs.  Key sequences which fail to parse will
diff --git a/XMonad/Util/ExclusiveScratchpads.hs b/XMonad/Util/ExclusiveScratchpads.hs
index a1d92016..1c9af1e0 100644
--- a/XMonad/Util/ExclusiveScratchpads.hs
+++ b/XMonad/Util/ExclusiveScratchpads.hs
@@ -36,9 +36,7 @@ module XMonad.Util.ExclusiveScratchpads (
   customFloating
   ) where
 
-import Control.Applicative (liftA2)
-import Control.Monad ((<=<),filterM)
-import Data.Monoid (appEndo)
+import XMonad.Prelude (appEndo, filterM, liftA2, (<=<))
 import XMonad
 import XMonad.Actions.Minimize
 import XMonad.Actions.TagWindows (addTag,delTag)
diff --git a/XMonad/Util/ExtensibleState.hs b/XMonad/Util/ExtensibleState.hs
index 5b6fe058..e620e331 100644
--- a/XMonad/Util/ExtensibleState.hs
+++ b/XMonad/Util/ExtensibleState.hs
@@ -31,7 +31,7 @@ import qualified Data.Map as M
 import XMonad.Core
 import XMonad.Util.PureX
 import qualified Control.Monad.State as State
-import Data.Maybe (fromMaybe)
+import XMonad.Prelude (fromMaybe)
 
 -- ---------------------------------------------------------------------
 -- $usage
diff --git a/XMonad/Util/Font.hs b/XMonad/Util/Font.hs
index 305f1ea6..dde80a6a 100644
--- a/XMonad/Util/Font.hs
+++ b/XMonad/Util/Font.hs
@@ -34,13 +34,12 @@ module XMonad.Util.Font
     ) where
 
 import XMonad
+import XMonad.Prelude
 import Foreign
 import Control.Exception as E
-import Data.Maybe
 import Text.Printf (printf)
 
 #ifdef XFT
-import Data.List
 import Graphics.X11.Xft
 import Graphics.X11.Xrender
 #endif
@@ -204,7 +203,3 @@ printStringXMF dpy drw fs@(Xft font) gc fc bc x y s = do
          \draw -> withXftColorName dpy visual colormap fc $
                    \color -> xftDrawString draw color font x y s
 #endif
-
--- | Short-hand for 'fromIntegral'
-fi :: (Integral a, Num b) => a -> b
-fi = fromIntegral
diff --git a/XMonad/Util/Hacks.hs b/XMonad/Util/Hacks.hs
index 7c2fd4ee..498e9a42 100644
--- a/XMonad/Util/Hacks.hs
+++ b/XMonad/Util/Hacks.hs
@@ -37,8 +37,7 @@ module XMonad.Util.Hacks (
 
 
 import XMonad
-import Data.Monoid (All(All))
-import Control.Monad (when, filterM)
+import XMonad.Prelude (All (All), filterM, when)
 import System.Posix.Env (putEnv)
 
 
diff --git a/XMonad/Util/Loggers.hs b/XMonad/Util/Loggers.hs
index 6b08a3a1..984c66a1 100644
--- a/XMonad/Util/Loggers.hs
+++ b/XMonad/Util/Loggers.hs
@@ -55,8 +55,7 @@ import XMonad.Util.Font (Align (..))
 import XMonad.Util.NamedWindows (getName)
 
 import Control.Exception as E
-import Data.List (find, isPrefixOf, isSuffixOf)
-import Data.Maybe (fromMaybe)
+import XMonad.Prelude (find, fromMaybe, isPrefixOf, isSuffixOf)
 import Data.Time (defaultTimeLocale, formatTime, getCurrentTime)
 import System.Directory (getDirectoryContents)
 import System.IO (hGetLine)
diff --git a/XMonad/Util/Loggers/NamedScratchpad.hs b/XMonad/Util/Loggers/NamedScratchpad.hs
index e7ca2284..4f2aea63 100644
--- a/XMonad/Util/Loggers/NamedScratchpad.hs
+++ b/XMonad/Util/Loggers/NamedScratchpad.hs
@@ -28,9 +28,7 @@ import Graphics.X11.Xlib.Extras (Event(..))
 import XMonad.Util.Loggers (Logger)
 import XMonad.Util.NamedScratchpad (NamedScratchpad(..))
 import qualified XMonad.Util.ExtensibleState as XS
-import Data.Monoid (All(..))
-import Data.Char (chr)
-import Control.Monad (forM, foldM)
+import XMonad.Prelude (All (..), chr, foldM, forM)
 import qualified Data.IntMap as M
 import qualified XMonad.StackSet as W (allWindows)
 
diff --git a/XMonad/Util/NamedActions.hs b/XMonad/Util/NamedActions.hs
index 31a15a44..cb3d7a0e 100644
--- a/XMonad/Util/NamedActions.hs
+++ b/XMonad/Util/NamedActions.hs
@@ -46,11 +46,11 @@ module XMonad.Util.NamedActions (
 
 
 import XMonad.Actions.Submap(submap)
+import XMonad.Prelude (groupBy)
 import XMonad
 import System.Posix.Process(executeFile)
 import Control.Arrow(Arrow((&&&), second, (***)))
 import Data.Bits(Bits((.&.), complement))
-import Data.List (groupBy)
 import System.Exit(ExitCode(ExitSuccess), exitWith)
 
 import qualified Data.Map as M
diff --git a/XMonad/Util/NamedScratchpad.hs b/XMonad/Util/NamedScratchpad.hs
index 9efd9e62..943e6a66 100644
--- a/XMonad/Util/NamedScratchpad.hs
+++ b/XMonad/Util/NamedScratchpad.hs
@@ -32,6 +32,7 @@ module XMonad.Util.NamedScratchpad (
   ) where
 
 import XMonad
+import XMonad.Prelude (filterM, listToMaybe, unless)
 import XMonad.Hooks.ManageHelpers (doRectFloat)
 import XMonad.Actions.DynamicWorkspaces (addHiddenWorkspace)
 import XMonad.Hooks.DynamicLog (PP, ppSort)
@@ -39,9 +40,6 @@ import XMonad.Actions.SpawnOn (spawnHere)
 
 import qualified Data.List.NonEmpty as NE
 
-import Control.Monad (filterM, unless)
-import Data.Maybe (listToMaybe)
-
 import qualified XMonad.StackSet as W
 
 
diff --git a/XMonad/Util/NamedWindows.hs b/XMonad/Util/NamedWindows.hs
index 197c20e3..a3f9dae6 100644
--- a/XMonad/Util/NamedWindows.hs
+++ b/XMonad/Util/NamedWindows.hs
@@ -24,7 +24,7 @@ module XMonad.Util.NamedWindows (
                                   ) where
 
 import Control.Exception as E
-import Data.Maybe ( fromMaybe, listToMaybe )
+import XMonad.Prelude ( fromMaybe, listToMaybe )
 
 import qualified XMonad.StackSet as W ( peek )
 
diff --git a/XMonad/Util/NoTaskbar.hs b/XMonad/Util/NoTaskbar.hs
index ce5795d1..1275c808 100644
--- a/XMonad/Util/NoTaskbar.hs
+++ b/XMonad/Util/NoTaskbar.hs
@@ -4,6 +4,7 @@ module XMonad.Util.NoTaskbar (-- * Usage
                              ,markNoTaskbar) where
 
 import XMonad.Core
+import XMonad.Prelude (fi)
 import XMonad.ManageHook
 import Graphics.X11.Xlib (Window)
 import Graphics.X11.Xlib.Atom (aTOM)
@@ -27,7 +28,3 @@ markNoTaskbar w = withDisplay $ \d -> do
                     ntb <- getAtom "_NET_WM_STATE_SKIP_TASKBAR"
                     npg <- getAtom "_NET_WM_STATE_SKIP_PAGER"
                     io $ changeProperty32 d w ws aTOM propModePrepend [fi ntb,fi npg]
-
--- sigh
-fi :: (Integral i, Num n) => i -> n
-fi = fromIntegral
diff --git a/XMonad/Util/Paste.hs b/XMonad/Util/Paste.hs
index 9e181e70..40accbed 100644
--- a/XMonad/Util/Paste.hs
+++ b/XMonad/Util/Paste.hs
@@ -27,8 +27,7 @@ import Graphics.X11
 import Graphics.X11.Xlib.Extras (none, setEventType, setKeyEvent)
 import Control.Monad.Reader (asks)
 import XMonad.Operations (withFocused)
-import Data.Char (isUpper)
-import Data.Maybe (listToMaybe)
+import XMonad.Prelude (isUpper, listToMaybe)
 import XMonad.Util.XSelection (getSelection)
 import XMonad.Util.EZConfig (parseKey)
 import Text.ParserCombinators.ReadP (readP_to_S)
diff --git a/XMonad/Util/PureX.hs b/XMonad/Util/PureX.hs
index 91e6c9ea..40fa1ec1 100644
--- a/XMonad/Util/PureX.hs
+++ b/XMonad/Util/PureX.hs
@@ -52,6 +52,7 @@ module XMonad.Util.PureX (
 
 -- xmonad
 import XMonad
+import XMonad.Prelude (Any (..), liftA2)
 import qualified XMonad.StackSet as W
 import qualified XMonad.Actions.FocusNth
 
@@ -59,10 +60,6 @@ import qualified XMonad.Actions.FocusNth
 import Control.Monad.State
 import Control.Monad.Reader
 
--- base
-import Data.Semigroup (Any(..))
-import Control.Applicative (liftA2)
-
 -- }}}
 
 -- --< Usage >-- {{{
@@ -291,4 +288,3 @@ focusNth :: XLike m => Int -> m Any
 focusNth i = focusWith (W.modify' (XMonad.Actions.FocusNth.focusNth' i))
 
 -- }}}
-
diff --git a/XMonad/Util/RemoteWindows.hs b/XMonad/Util/RemoteWindows.hs
index dd15b493..bd4605aa 100644
--- a/XMonad/Util/RemoteWindows.hs
+++ b/XMonad/Util/RemoteWindows.hs
@@ -38,8 +38,7 @@ module XMonad.Util.RemoteWindows
 
 import XMonad
 import XMonad.Util.WindowProperties
-import Data.Maybe
-import Control.Monad
+import XMonad.Prelude
 import System.Posix.Env
 
 -- $usage
diff --git a/XMonad/Util/Replace.hs b/XMonad/Util/Replace.hs
index 49eda824..f89e68ab 100644
--- a/XMonad/Util/Replace.hs
+++ b/XMonad/Util/Replace.hs
@@ -28,8 +28,7 @@ module XMonad.Util.Replace
     ) where
 
 import XMonad
-import Data.Function
-import Control.Monad
+import XMonad.Prelude
 
 -- $usage
 -- You must run the 'replace' action before starting xmonad proper, this
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 8c3e57b8..cb67cbc1 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -40,7 +40,7 @@ import Control.Concurrent (threadDelay)
 import System.IO
 import System.Process (runInteractiveProcess)
 import XMonad
-import Control.Monad
+import XMonad.Prelude
 
 -- $usage
 -- For an example usage of 'runInTerm' see "XMonad.Prompt.Ssh"
diff --git a/XMonad/Util/SessionStart.hs b/XMonad/Util/SessionStart.hs
index f5f7b13d..deb900d7 100644
--- a/XMonad/Util/SessionStart.hs
+++ b/XMonad/Util/SessionStart.hs
@@ -22,7 +22,7 @@ module XMonad.Util.SessionStart
     )
 where
 
-import Control.Monad (when)
+import XMonad.Prelude (when)
 
 import XMonad
 import qualified XMonad.Util.ExtensibleState as XS
diff --git a/XMonad/Util/SpawnNamedPipe.hs b/XMonad/Util/SpawnNamedPipe.hs
index 1e936394..579787e2 100644
--- a/XMonad/Util/SpawnNamedPipe.hs
+++ b/XMonad/Util/SpawnNamedPipe.hs
@@ -25,7 +25,7 @@ import XMonad
 import XMonad.Util.Run
 import System.IO
 import qualified XMonad.Util.ExtensibleState as XS
-import Control.Monad
+import XMonad.Prelude
 import qualified Data.Map as Map
 
 -- $usage
diff --git a/XMonad/Util/SpawnOnce.hs b/XMonad/Util/SpawnOnce.hs
index df935097..00f221fd 100644
--- a/XMonad/Util/SpawnOnce.hs
+++ b/XMonad/Util/SpawnOnce.hs
@@ -21,7 +21,7 @@ import XMonad
 import XMonad.Actions.SpawnOn
 import Data.Set as Set
 import qualified XMonad.Util.ExtensibleState as XS
-import Control.Monad
+import XMonad.Prelude
 
 data SpawnOnce = SpawnOnce { unspawnOnce :: (Set String) }
     deriving (Read, Show, Typeable)
diff --git a/XMonad/Util/Stack.hs b/XMonad/Util/Stack.hs
index a9765330..12382cc5 100644
--- a/XMonad/Util/Stack.hs
+++ b/XMonad/Util/Stack.hs
@@ -80,10 +80,7 @@ module XMonad.Util.Stack ( -- * Usage
                          ) where
 
 import qualified XMonad.StackSet as W
-import Control.Applicative ((<|>))
-import Control.Monad (guard)
-import Data.List (sortBy)
-
+import XMonad.Prelude (guard, sortBy, (!?), (<|>))
 
 
 type Zipper a = Maybe (W.Stack a)
@@ -328,9 +325,8 @@ elemZ a as = foldlZ_ step False as
 
 -- | Safe version of '!!'
 getI :: Int -> [a] -> Maybe a
-getI _ [] = Nothing
-getI 0 (a:_) = Just a
-getI i (_:as) = getI (i-1) as
+getI i xs = xs !? i
+{-# DEPRECATED getI "Use XMonad.Prelude.(!?) instead." #-}
 
 -- | Map a function across both 'Left's and 'Right's.
 -- The 'Bool' argument is 'True' in a 'Right', 'False'
diff --git a/XMonad/Util/WindowProperties.hs b/XMonad/Util/WindowProperties.hs
index c4243bdd..be1bdec9 100644
--- a/XMonad/Util/WindowProperties.hs
+++ b/XMonad/Util/WindowProperties.hs
@@ -22,10 +22,10 @@ module XMonad.Util.WindowProperties (
     getProp32, getProp32s)
 where
 
-import Control.Monad
 import Foreign.C.Types (CLong)
 import XMonad
 import XMonad.Actions.TagWindows (hasTag)
+import XMonad.Prelude (filterM)
 import qualified XMonad.StackSet as W
 
 -- $edsl
diff --git a/XMonad/Util/WorkspaceCompare.hs b/XMonad/Util/WorkspaceCompare.hs
index ccfe6f70..3858b34a 100644
--- a/XMonad/Util/WorkspaceCompare.hs
+++ b/XMonad/Util/WorkspaceCompare.hs
@@ -25,10 +25,8 @@ module XMonad.Util.WorkspaceCompare ( WorkspaceCompare, WorkspaceSort
 
 import XMonad
 import qualified XMonad.StackSet as S
-import Data.List
-import Data.Maybe
+import XMonad.Prelude
 import XMonad.Actions.PhysicalScreens (ScreenComparator(ScreenComparator), getScreenIdAndRectangle, screenComparatorById)
-import Data.Function (on)
 
 type WorkspaceCompare = WorkspaceId -> WorkspaceId -> Ordering
 type WorkspaceSort = [WindowSpace] -> [WindowSpace]
diff --git a/XMonad/Util/XSelection.hs b/XMonad/Util/XSelection.hs
index 3ddcad9e..79ad13ae 100644
--- a/XMonad/Util/XSelection.hs
+++ b/XMonad/Util/XSelection.hs
@@ -23,8 +23,8 @@ module XMonad.Util.XSelection (  -- * Usage
                                  transformSafePromptSelection) where
 
 import Control.Exception as E (catch,SomeException(..))
-import Data.Maybe (fromMaybe)
 import XMonad
+import XMonad.Prelude (fromMaybe)
 import XMonad.Util.Run (safeSpawn, unsafeSpawn)
 
 import Codec.Binary.UTF8.String (decode)
diff --git a/XMonad/Util/XUtils.hs b/XMonad/Util/XUtils.hs
index b12a6112..b2163d50 100644
--- a/XMonad/Util/XUtils.hs
+++ b/XMonad/Util/XUtils.hs
@@ -32,11 +32,10 @@ module XMonad.Util.XUtils
     , fi
     ) where
 
-import Data.Maybe
+import XMonad.Prelude
 import XMonad
 import XMonad.Util.Font
 import XMonad.Util.Image
-import Control.Monad
 
 -- $usage
 -- See "XMonad.Layout.Tabbed" or "XMonad.Layout.DragPane" or
diff --git a/tests/XPrompt.hs b/tests/XPrompt.hs
index dff8099a..40801347 100644
--- a/tests/XPrompt.hs
+++ b/tests/XPrompt.hs
@@ -9,6 +9,7 @@ module XPrompt where
 
 import Test.QuickCheck
 
+import XMonad.Prelude (chunksOf)
 import XMonad.Prompt
 import qualified XMonad.Prompt.Shell as S
 
@@ -20,7 +21,7 @@ prop_split (str :: String) =
 -- of the string.
 prop_spliInSubListsAt (x :: Int) (str :: String) =
     x < length str ==> result == take x str
-    where result = case splitInSubListsAt x str of
+    where result = case chunksOf x str of
                      [] -> []
                      x -> head x
 
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index ba142556..3dd6c651 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -298,6 +298,7 @@ library
                         XMonad.Layout.WindowSwitcherDecoration
                         XMonad.Layout.WorkspaceDir
                         XMonad.Layout.ZoomRow
+                        XMonad.Prelude
                         XMonad.Prompt
                         XMonad.Prompt.AppLauncher
                         XMonad.Prompt.AppendFile