-- A fix to refocus windows in a sublayout -- copied and manipulated from https://github.com/wz1000/xmonad-config/blob/master/xmonad.hs -- thx wz1000 {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} module TabbedFix (historyLayout, runAllPending) where import XMonad import qualified XMonad.StackSet as W import qualified Data.List as L import qualified XMonad.Util.ExtensibleState as ES import Control.DeepSeq (force) import XMonad.Layout.LayoutModifier (LayoutModifier, ModifiedLayout(ModifiedLayout), modifyLayout) newtype PendingActions = PendingActions { getPending :: [X()] } instance ExtensionClass PendingActions where initialValue = PendingActions [] -- Add action to stack addAction :: X () -> X () addAction x = ES.modify (\(PendingActions xs) -> PendingActions (x:xs)) runAllPending :: X () runAllPending = do PendingActions actions <- ES.get ES.put (PendingActions []) sequence_ actions newtype FocusHistory = FocusHistory { getFocusHistory :: [Window] } deriving (Read, Show, Typeable) instance ExtensionClass FocusHistory where initialValue = FocusHistory [] extensionType = PersistentExtension data FocusLayout a = FocusLayout deriving (Read,Show,Typeable) historyLayout :: l Window -> ModifiedLayout FocusLayout l Window historyLayout = ModifiedLayout FocusLayout instance LayoutModifier FocusLayout Window where modifyLayout fh ws rct = do wold <- getFocused history <- getFocusHistory <$> ES.get wnew <- windowHistoryHook wold case wnew of Nothing -> runLayout ws rct Just w -> do let oldstack = W.stack ws let mw = L.find (`elem` W.integrate' oldstack) history let newstack = if (w `elem` (W.integrate' oldstack)) then until ((w==) . W.focus) W.focusUp' <$> oldstack else case mw of Just w -> until ((w==) . W.focus) W.focusUp' <$> oldstack Nothing -> oldstack modifyWindowSet (W.focusWindow w) addAction $ do maybe (return ()) makeBorderNormal wold windows id runLayout ws{W.stack = newstack} rct windowHistoryHook Nothing = return Nothing windowHistoryHook (Just w) = do hist <- getFocusHistory <$> ES.get curws <- gets $ W.index . windowset withWindowSet $ \allws -> case hist of [] -> do ES.put $ FocusHistory[w] return Nothing (prev:xs) | prev == w -> return Nothing -- Previous focus was removed from ws, focus on previous existing window in current ws | not (prev `elem` curws) -> do let hist' = filter (`W.member` allws) xs ES.put (FocusHistory $ force $ hist') return $ L.find (\x -> x `elem` curws ) hist' -- Add current focus to history | otherwise -> do ES.put $ FocusHistory $ force $ (w:L.delete w hist) return Nothing makeBorderRed :: Window -> X () makeBorderRed w = withDisplay $ \d -> io $ do setWindowBorder d w 0xff0000 -- wz1000: palo: btw, you will need to change the color in makeBorderNormal to your unfocused border color makeBorderNormal w = withDisplay $ \d -> io $ do setWindowBorder d w 0x2b2b2b makeBorderFocused w = withDisplay $ \d -> io $ do setWindowBorder d w 0xcccccc getFocused :: X (Maybe Window) getFocused = withWindowSet (return . W.peek)