diff --git a/XMonad/Actions/CopyWindow.hs b/XMonad/Actions/CopyWindow.hs
index 68835e8a..68d6e387 100644
--- a/XMonad/Actions/CopyWindow.hs
+++ b/XMonad/Actions/CopyWindow.hs
@@ -77,7 +77,7 @@ copyToAll s = foldr copy s $ map tag (workspaces s)
 copyWindow :: (Eq a, Eq i, Eq s) => a -> i -> StackSet i l a s sd -> StackSet i l a s sd
 copyWindow w n = copy'
     where copy' s = if n `tagMember` s
-                    then view (tag (workspace (current s))) $ insertUp' w $ view n s
+                    then view (currentTag s) $ insertUp' w $ view n s
                     else s
           insertUp' a s = modify (Just $ Stack a [] [])
                           (\(Stack t l r) -> if a `elem` t:l++r
@@ -107,7 +107,7 @@ kill1 = do ss <- gets windowset
 killAllOtherCopies :: X ()
 killAllOtherCopies = do ss <- gets windowset
                         whenJust (peek ss) $ \w -> windows $
-                                                   view (tag (workspace (current ss))) .
+                                                   view (currentTag ss) .
                                                    delFromAllButCurrent w
     where
       delFromAllButCurrent w ss = foldr ($) ss $
diff --git a/XMonad/Actions/CycleWS.hs b/XMonad/Actions/CycleWS.hs
index ac0fddb6..f7a59bb1 100644
--- a/XMonad/Actions/CycleWS.hs
+++ b/XMonad/Actions/CycleWS.hs
@@ -217,7 +217,7 @@ findWorkspace s dir t n = findWorkspaceGen s (wsTypeToPred t) (maybeNegate dir n
     maybeNegate Prev d = (-d)
 
 findWorkspaceGen :: X WorkspaceSort -> X (WindowSpace -> Bool) -> Int -> X WorkspaceId
-findWorkspaceGen _ _ 0 = (tag . workspace . current) `fmap` gets windowset
+findWorkspaceGen _ _ 0 = gets (currentTag . windowset)
 findWorkspaceGen sortX wsPredX d = do
     wsPred <- wsPredX
     sort   <- sortX
diff --git a/XMonad/Actions/PerWorkspaceKeys.hs b/XMonad/Actions/PerWorkspaceKeys.hs
index 9dd6a5da..dcf1a9b4 100644
--- a/XMonad/Actions/PerWorkspaceKeys.hs
+++ b/XMonad/Actions/PerWorkspaceKeys.hs
@@ -36,7 +36,7 @@ import Data.List (find)
 
 -- | Uses supplied function to decide which action to run depending on current workspace name.
 chooseAction :: (String->X()) -> X()
-chooseAction f = withWindowSet (f . S.tag . S.workspace . S.current)
+chooseAction f = withWindowSet (f . S.currentTag)
 
 -- | If current workspace is listed, run appropriate action (only the first match counts!)
 -- If it isn't listed, then run default action (marked with empty string, \"\"), or do nothing if default isn't supplied.
diff --git a/XMonad/Actions/SwapWorkspaces.hs b/XMonad/Actions/SwapWorkspaces.hs
index c9b1143e..9890ef23 100644
--- a/XMonad/Actions/SwapWorkspaces.hs
+++ b/XMonad/Actions/SwapWorkspaces.hs
@@ -48,7 +48,7 @@ import XMonad.Util.WorkspaceCompare
 -- | Swaps the currently focused workspace with the given workspace tag, via
 --   @swapWorkspaces@.
 swapWithCurrent :: Eq i => i -> StackSet i l a s sd -> StackSet i l a s sd
-swapWithCurrent t s = swapWorkspaces t (tag $ workspace $ current s) s
+swapWithCurrent t s = swapWorkspaces t (currentTag s) s
 
 -- | Say @swapTo Next@ or @swapTo Prev@ to move your current workspace.
 -- This is an @X ()@ so can be hooked up to your keybindings directly.
diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs
index 4501e7d2..01ea1d84 100644
--- a/XMonad/Actions/TagWindows.hs
+++ b/XMonad/Actions/TagWindows.hs
@@ -120,7 +120,7 @@ wsToList ws = crs ++ cls
 wsToListGlobal :: (Ord i) => StackSet i l a s sd -> [a]
 wsToListGlobal ws = concat ([crs] ++ rws ++ lws ++ [cls])
     where
-        curtag = tag . workspace . current $ ws
+        curtag = currentTag ws
         (crs, cls) = (cms down, cms (reverse . up))
         cms f = maybe [] f (stack . workspace . current $ ws)
         (lws, rws) = (mws (<), mws (>))
@@ -149,8 +149,7 @@ withTagged       t f = withTagged'       t (mapM_ f)
 withTaggedGlobal t f = withTaggedGlobal' t (mapM_ f)
 
 withTagged' :: String -> ([Window] -> X ()) -> X ()
-withTagged' t m = gets windowset >>=
-    filterM (hasTag t) . integrate' . stack . workspace . current >>= m
+withTagged' t m = gets windowset >>= filterM (hasTag t) . index >>= m
 
 withTaggedGlobal' :: String -> ([Window] -> X ()) -> X ()
 withTaggedGlobal' t m = gets windowset >>=
@@ -160,7 +159,7 @@ withFocusedP :: (Window -> WindowSet -> WindowSet) -> X ()
 withFocusedP f = withFocused $ windows . f
 
 shiftHere :: (Ord a, Eq s, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
-shiftHere w s = shiftWin (tag . workspace . current $ s) w s
+shiftHere w s = shiftWin (currentTag s) w s
 
 shiftToScreen :: (Ord a, Eq s, Eq i) => s -> a -> StackSet i l a s sd -> StackSet i l a s sd
 shiftToScreen sid w s = case filter (\m -> sid /= screen m) ((current s):(visible s)) of
diff --git a/XMonad/Actions/WindowBringer.hs b/XMonad/Actions/WindowBringer.hs
index 83ba4810..102c15bf 100644
--- a/XMonad/Actions/WindowBringer.hs
+++ b/XMonad/Actions/WindowBringer.hs
@@ -57,7 +57,7 @@ bringMenu = actionMenu bringWindow
 
 -- | Brings the specified window into the current workspace.
 bringWindow :: Window -> X.WindowSet -> X.WindowSet
-bringWindow w ws = W.shiftWin (W.tag . W.workspace . W.current $ ws) w ws
+bringWindow w ws = W.shiftWin (W.currentTag ws) w ws
 
 -- | Calls dmenuMap to grab the appropriate Window, and hands it off to action
 --   if found.
diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs
index 88c4db14..99b61b65 100644
--- a/XMonad/Actions/WindowNavigation.hs
+++ b/XMonad/Actions/WindowNavigation.hs
@@ -153,7 +153,7 @@ currentPosition posRef = do
     currentWindow <- gets (W.peek . windowset)
     currentRect <- maybe (Rectangle 0 0 0 0) snd <$> windowRect (fromMaybe root currentWindow)
 
-    wsid <- gets (W.tag . W.workspace . W.current . windowset)
+    wsid <- gets (W.currentTag . windowset)
     mp <- M.lookup wsid <$> io (readIORef posRef)
 
     return $ maybe (middleOf currentRect) (`inside` currentRect) mp
@@ -162,7 +162,7 @@ currentPosition posRef = do
 
 setPosition :: IORef WNState -> Point -> Rectangle -> X ()
 setPosition posRef oldPos newRect = do
-    wsid <- gets (W.tag . W.workspace . W.current . windowset)
+    wsid <- gets (W.currentTag . windowset)
     io $ modifyIORef posRef $ M.insert wsid (oldPos `inside` newRect)
 
 inside :: Point -> Rectangle -> Point
diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs
index 8a10fb2f..a78947be 100644
--- a/XMonad/Config/Droundy.hs
+++ b/XMonad/Config/Droundy.hs
@@ -176,7 +176,7 @@ instance UrgencyHook FocusUrgencyHook Window where
                       s { windowset = until ((Just w ==) . W.peek)
                                       W.focusUp $ windowset s }
                   | otherwise =
-                      let t = W.tag $ W.workspace $ W.current $ windowset s
+                      let t = W.currentTag $ windowset s
                       in s { windowset = until ((Just w ==) . W.peek)
                              W.focusUp $ copyWindow w t $ windowset s }
               has _ Nothing         = False
diff --git a/XMonad/Hooks/DynamicLog.hs b/XMonad/Hooks/DynamicLog.hs
index d0696dc2..db16042d 100644
--- a/XMonad/Hooks/DynamicLog.hs
+++ b/XMonad/Hooks/DynamicLog.hs
@@ -256,7 +256,7 @@ dynamicLogString pp = do
 pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String
 pprWindowSet sort' urgents pp s = sepBy (ppWsSep pp) . map fmt . sort' $
             map S.workspace (S.current s : S.visible s) ++ S.hidden s
-   where this     = S.tag (S.workspace (S.current s))
+   where this     = S.currentTag s
          visibles = map (S.tag . S.workspace) (S.visible s)
 
          fmt w = printer pp (S.tag w)
diff --git a/XMonad/Hooks/EventHook.hs b/XMonad/Hooks/EventHook.hs
index 0022386d..234de48c 100644
--- a/XMonad/Hooks/EventHook.hs
+++ b/XMonad/Hooks/EventHook.hs
@@ -29,11 +29,10 @@ module XMonad.Hooks.EventHook
     , HandleEvent
     ) where
 
-import Control.Applicative ((<$>))
 import Data.Maybe
 
 import XMonad
-import XMonad.StackSet (StackSet (..), Screen (..), Workspace (..))
+import XMonad.StackSet (Workspace (..), currentTag)
 
 -- $usage
 -- You can use this module with the following in your
@@ -89,7 +88,7 @@ instance Message EventHandleMsg
 instance (EventHook eh, LayoutClass l a) => LayoutClass (HandleEvent eh l) a where
     runLayout (Workspace i (HandleEvent Nothing True eh l) ms) r = do
       broadcastMessage HandlerOff
-      iws       <- (tag . workspace . current) <$> gets windowset
+      iws       <- gets (currentTag . windowset)
       (wrs, ml) <- runLayout (Workspace i l ms) r
       return (wrs, Just $ HandleEvent (Just iws) True eh (fromMaybe l ml))
 
diff --git a/XMonad/Hooks/EwmhDesktops.hs b/XMonad/Hooks/EwmhDesktops.hs
index 83a05a62..6eec3bfd 100644
--- a/XMonad/Hooks/EwmhDesktops.hs
+++ b/XMonad/Hooks/EwmhDesktops.hs
@@ -83,7 +83,7 @@ ewmhDesktopsLogHookCustom f = withWindowSet $ \s -> do
     setDesktopNames (map W.tag ws)
 
     -- Current desktop
-    let curr = fromJust $ elemIndex (W.tag (W.workspace (W.current s))) $ map W.tag ws
+    let curr = fromJust $ elemIndex (W.currentTag s) $ map W.tag ws
 
     setCurrentDesktop curr
 
diff --git a/XMonad/Layout/ShowWName.hs b/XMonad/Layout/ShowWName.hs
index f9968616..0aeeb328 100644
--- a/XMonad/Layout/ShowWName.hs
+++ b/XMonad/Layout/ShowWName.hs
@@ -89,7 +89,7 @@ doShow (SWN False _  _          ) _ wrs = return (wrs, Nothing)
 flashName :: SWNConfig -> Rectangle -> [(a, Rectangle)] -> X ([(a, Rectangle)], Maybe (ShowWName a))
 flashName c (Rectangle _ _ wh ht) wrs = do
   d <- asks display
-  n <- withWindowSet (return . S.tag . S.workspace . S.current)
+  n <- withWindowSet (return . S.currentTag)
   f <- initXMF (swn_font c)
   width   <- textWidthXMF d f n
   (as,ds) <- textExtentsXMF f n
diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs
index 46473907..abb2d7e4 100644
--- a/XMonad/Layout/WorkspaceDir.hs
+++ b/XMonad/Layout/WorkspaceDir.hs
@@ -37,7 +37,7 @@ import XMonad.Util.Run ( runProcessWithInput )
 import XMonad.Prompt ( XPConfig )
 import XMonad.Prompt.Directory ( directoryPrompt )
 import XMonad.Layout.LayoutModifier
-import XMonad.StackSet ( tag, current, workspace )
+import XMonad.StackSet ( tag, currentTag )
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -69,7 +69,7 @@ instance Message Chdir
 data WorkspaceDir a = WorkspaceDir String deriving ( Read, Show )
 
 instance LayoutModifier WorkspaceDir Window where
-    modifyLayout (WorkspaceDir d) w r = do tc <- gets (tag.workspace.current.windowset)
+    modifyLayout (WorkspaceDir d) w r = do tc <- gets (currentTag.windowset)
                                            when (tc == tag w) $ scd d
                                            runLayout w r
     handleMess (WorkspaceDir _) m