nixos-config/system/desktop/home-manager/xmonad/TabbedFix.hs

113 lines
4 KiB
Haskell
Raw Normal View History

2019-10-24 02:20:38 +02:00
{-# LANGUAGE MultiParamTypeClasses #-}
2019-11-10 18:13:03 +01:00
{-# LANGUAGE TypeSynonymInstances #-}
2019-10-24 02:20:38 +02:00
module TabbedFix (historyLayout, runAllPending) where
2019-11-10 18:13:03 +01:00
import Control.DeepSeq (force)
import qualified Data.List as L
import XMonad
import XMonad.Layout.LayoutModifier (LayoutModifier,
ModifiedLayout (ModifiedLayout),
modifyLayout)
import qualified XMonad.StackSet as W
import qualified XMonad.Util.ExtensibleState as ES
newtype PendingActions =
PendingActions [X ()]
2019-10-24 02:20:38 +02:00
instance ExtensionClass PendingActions where
initialValue = PendingActions []
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
2019-11-10 18:13:03 +01:00
modifyLayout _ workspace rectangle = do
2019-11-12 00:49:27 +01:00
currentFocusedWindow <- getFocused
windowHistory <- getFocusHistory <$> ES.get
newWindow <- windowHistoryHook currentFocusedWindow
2019-11-10 18:13:03 +01:00
case newWindow of
Nothing -> runLayout workspace rectangle
Just window -> do
2019-11-12 00:49:27 +01:00
let currentStack = W.stack workspace
let lastFocusedWindow =
L.find (`elem` W.integrate' currentStack) windowHistory
let focusWindow windowToFocus =
until ((windowToFocus ==) . W.focus) W.focusUp' <$> currentStack
2019-11-10 18:13:03 +01:00
let newstack =
2019-11-12 00:49:27 +01:00
if window `elem` W.integrate' currentStack
then focusWindow window
else case lastFocusedWindow of
Just window' -> focusWindow window'
Nothing -> currentStack
2019-11-10 18:13:03 +01:00
modifyWindowSet (W.focusWindow window)
2019-10-24 02:20:38 +02:00
addAction $ do
2019-11-12 00:49:27 +01:00
maybe (return ()) makeBorderNormal currentFocusedWindow
2019-10-24 02:20:38 +02:00
windows id
2019-11-10 18:13:03 +01:00
runLayout workspace {W.stack = newstack} rectangle
2019-10-24 02:20:38 +02:00
2019-11-10 18:13:03 +01:00
windowHistoryHook :: Maybe Window -> X (Maybe Window)
2019-10-24 02:20:38 +02:00
windowHistoryHook Nothing = return Nothing
2019-11-12 00:49:27 +01:00
windowHistoryHook (Just currentFocusedWindow) = do
currentWindows <- gets $ W.index . windowset
windowHistory <- getFocusHistory <$> ES.get
withWindowSet $ \windowSet ->
case windowHistory of
2019-10-24 02:20:38 +02:00
[] -> do
2019-11-12 00:49:27 +01:00
ES.put $ FocusHistory [currentFocusedWindow]
2019-10-24 02:20:38 +02:00
return Nothing
2019-11-12 00:49:27 +01:00
(prevFocusedWindow:focusedWindows)
| prevFocusedWindow == currentFocusedWindow -> return Nothing
-- Previous focus was removed from windowSet focus on previous existing window in current windowSet
| prevFocusedWindow `notElem` currentWindows -> do
let windowHistory' = filter (`W.member` windowSet) focusedWindows
ES.put (FocusHistory $ force windowHistory')
return $ L.find (`elem` currentWindows) windowHistory'
-- Add current focus to windowHistory
2019-11-10 18:13:03 +01:00
| otherwise -> do
2019-11-12 00:49:27 +01:00
ES.put $
FocusHistory $
force $
currentFocusedWindow : L.delete currentFocusedWindow windowHistory
2019-11-10 18:13:03 +01:00
return Nothing
2019-10-24 02:20:38 +02:00
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
2019-11-10 18:13:03 +01:00
makeBorderNormal :: Window -> X ()
2019-10-24 02:20:38 +02:00
makeBorderNormal w =
withDisplay $ \d -> io $ do
setWindowBorder d w 0x2b2b2b
2019-11-10 18:13:03 +01:00
makeBorderFocused :: Window -> X ()
2019-10-24 02:20:38 +02:00
makeBorderFocused w =
withDisplay $ \d -> io $ do
setWindowBorder d w 0xcccccc
getFocused :: X (Maybe Window)
getFocused = withWindowSet (return . W.peek)