diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs
index 6fa76f76..fd1a7c77 100644
--- a/XMonad/Config/Droundy.hs
+++ b/XMonad/Config/Droundy.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE TupleSections #-}
 {-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-orphans #-}
 -----------------------------------------------------------------------------
 -- |
@@ -114,9 +115,9 @@ keys x = M.fromList $
     ]
 
     ++
-    zip (zip (repeat $ modMask x) [xK_F1..xK_F12]) (map (withNthWorkspace W.greedyView) [0..])
+    zip (map (modMask x,) [xK_F1..xK_F12]) (map (withNthWorkspace W.greedyView) [0..])
     ++
-    zip (zip (repeat (modMask x .|. shiftMask)) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
+    zip (map (modMask x .|. shiftMask,) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
 
 config = docks $ ewmh def
          { borderWidth = 1 -- Width of the window border in pixels.
diff --git a/XMonad/Hooks/Place.hs b/XMonad/Hooks/Place.hs
index 19bfbaa5..a25b0772 100644
--- a/XMonad/Hooks/Place.hs
+++ b/XMonad/Hooks/Place.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE TupleSections #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  XMonad.Hooks.Place
@@ -188,7 +189,7 @@ placeHook p = do window <- ask
                       let infos = filter ((window `elem`) . stackContents . S.stack . fst)
                                      $ [screenInfo $ S.current theWS]
                                         ++ map screenInfo (S.visible theWS)
-                                        ++ zip (S.hidden theWS) (repeat currentRect)
+                                        ++ map (, currentRect) (S.hidden theWS)
 
                       guard(not $ null infos)
 
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs
index eadb1079..f9225510 100644
--- a/XMonad/Layout/Decoration.hs
+++ b/XMonad/Layout/Decoration.hs
@@ -1,8 +1,9 @@
+{-# LANGUAGE CPP                   #-}
 {-# LANGUAGE FlexibleContexts      #-}
 {-# LANGUAGE FlexibleInstances     #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE PatternGuards         #-}
-{-# LANGUAGE CPP                   #-}
+{-# LANGUAGE TupleSections         #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  XMonad.Layout.Decoration
@@ -241,7 +242,7 @@ instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration d
                                     toDel = todel d dwrs
                                     toAdd = toadd a wrs
                                 deleteDecos (map snd toDel)
-                                let ndwrs = zip toAdd $ repeat (Nothing,Nothing)
+                                let ndwrs = map (, (Nothing,Nothing)) toAdd
                                 ndecos <- resync (ndwrs ++ del_dwrs d dwrs) wrs
                                 processState (s {decos = ndecos })
 
diff --git a/XMonad/Layout/Simplest.hs b/XMonad/Layout/Simplest.hs
index 1e8c09b9..74545736 100644
--- a/XMonad/Layout/Simplest.hs
+++ b/XMonad/Layout/Simplest.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE TupleSections #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  XMonad.Layout.Simplest
@@ -39,4 +41,4 @@ import qualified XMonad.StackSet as S
 
 data Simplest a = Simplest deriving (Show, Read)
 instance LayoutClass Simplest a where
-    pureLayout Simplest rec (S.Stack w l r) = zip (w : reverse l ++ r) (repeat rec)
+    pureLayout Simplest rec (S.Stack w l r) = map (, rec) (w : reverse l ++ r)
diff --git a/XMonad/Layout/SubLayouts.hs b/XMonad/Layout/SubLayouts.hs
index 1fc52163..49556119 100644
--- a/XMonad/Layout/SubLayouts.hs
+++ b/XMonad/Layout/SubLayouts.hs
@@ -4,6 +4,7 @@
 {-# LANGUAGE ParallelListComp #-}
 {-# LANGUAGE PatternGuards #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TupleSections #-}
 {-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
@@ -347,7 +348,7 @@ instance forall l. (Read (l Window), Show (l Window), LayoutClass l Window) => L
             return $ Just $ Sublayout (I ((sm,w):ms)) defl sls
 
         | Just (Broadcast sm) <- fromMessage m = do
-            ms' <- fmap (zip (repeat sm) . W.integrate') currentStack
+            ms' <- fmap (map (sm,) . W.integrate') currentStack
             return $ if null ms' then Nothing
                 else Just $ Sublayout (I $ ms' ++ ms) defl sls
 
@@ -408,7 +409,7 @@ instance forall l. (Read (l Window), Show (l Window), LayoutClass l Window) => L
            catchLayoutMess :: LayoutMessages -> X (Maybe (Sublayout l Window))
            catchLayoutMess x = do
             let m' = x `asTypeOf` (undefined :: LayoutMessages)
-            ms' <- zip (repeat $ SomeMessage m') . W.integrate'
+            ms' <- map (SomeMessage m',) . W.integrate'
                     <$> currentStack
             return $ do guard $ not $ null ms'
                         Just $ Sublayout (I $ ms' ++ ms) defl sls
diff --git a/XMonad/Util/EZConfig.hs b/XMonad/Util/EZConfig.hs
index 904908e4..ecc13f2b 100644
--- a/XMonad/Util/EZConfig.hs
+++ b/XMonad/Util/EZConfig.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE CPP #-}
+{-# LANGUAGE TupleSections #-}
 --------------------------------------------------------------------
 -- |
 -- Module      :  XMonad.Util.EZConfig
@@ -123,7 +124,7 @@ removeKeys conf keyList =
 
 removeKeysP :: XConfig l -> [String] -> XConfig l
 removeKeysP conf keyList =
-    conf { keys = \cnf -> keys conf cnf `M.difference` mkKeymap cnf (zip keyList $ repeat (return ())) }
+    conf { keys = \cnf -> keys conf cnf `M.difference` mkKeymap cnf (map (, return ()) keyList) }
 
 -- | Like 'additionalKeys', but for mouse bindings.
 additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a