{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} import Data.Maybe import qualified Data.Map as M import qualified Data.Set as S import XMonad import qualified XMonad.Actions.CycleWS as CWS import qualified XMonad.Actions.WindowNavigation as WN import qualified XMonad.Config.Gnome as CG import qualified XMonad.Hooks.EwmhDesktops as ED import qualified XMonad.Hooks.ManageDocks as MD import qualified XMonad.Layout.DwmStyle as DS import qualified XMonad.Layout.LayoutCombinators as LC import qualified XMonad.Layout.NoBorders as NB import qualified XMonad.Layout.Tabbed as LT import qualified XMonad.Layout.ThreeColumns as TC import qualified XMonad.Operations as Op import qualified XMonad.StackSet as SS data (Show a, Read a) => Sliced a = Sliced Int -- number of windows visible (Maybe a) -- focused window [Maybe a] -- visible windows deriving (Show, Read) fillInBlanks :: [Maybe a] -> [a] -> [Maybe a] fillInBlanks [] _ = [] fillInBlanks xs [] = xs fillInBlanks ((Just x):xs) ys = (Just x):(fillInBlanks xs ys) fillInBlanks (Nothing:xs) (y:ys) = (Just y):(fillInBlanks xs ys) instance (Eq a, Show a, Read a) => LayoutClass Sliced a where doLayout (Sliced numVisible focused visible) rect st = return (tile, Just $ next) where wasFocused w = case focused of Just f -> w == f Nothing -> False fixLength v = take numVisible $ v ++ noth where noth = Nothing : noth switchToNewFocused v = if (Just $ SS.focus st) `elem` v then v else map repl v where repl Nothing = Nothing repl (Just w) = Just (if wasFocused w then (SS.focus st) else w) replaceEmptyWithFocused v = if (Just $ SS.focus st) `elem` v then v else fillInBlanks v [SS.focus st] replaceRightmostWithFocused v = if (Just $ SS.focus st) `elem` v then v else reverse $ (Just $ SS.focus st) : (tail $ reverse v) removeDeleted v = map filt v where filt Nothing = Nothing filt (Just w) = if w `elem` (SS.integrate st) then (Just w) else Nothing fillEmptySlots v = fillInBlanks v hidden where hidden = filter (`notElem` (catMaybes v)) (SS.integrate st) visible' = fillEmptySlots $ removeDeleted $ replaceRightmostWithFocused $ replaceEmptyWithFocused $ switchToNewFocused $ fixLength visible tile = zip toDraw $ splitHorizontally (length toDraw) rect where toDraw = catMaybes visible' next = Sliced numVisible (Just $ SS.focus st) visible' handleMessage (Sliced numVisible focused visible) x = return $ case fromMessage x of Just Shrink -> Just (Sliced (numVisible - 1) focused visible) Just Expand -> Just (Sliced (numVisible + 1) focused visible) _ -> Nothing description _ = "Sliced" -- Shift focus one step. shiftOne :: SS.Stack a -> SS.Stack a shiftOne (SS.Stack t ls (r:rs)) = SS.Stack r (t:ls) rs shiftOne (SS.Stack t ls []) = SS.Stack x [] xs where (x:xs) = reverse (t:ls) -- Shift focus to next unmapped window. focusNextUnmapped :: X () focusNextUnmapped = do state <- get let visible = mapped state Op.windows $ SS.modify' $ skipWindows visible where skipWindows wins st@(SS.Stack t _ _) = if S.member t wins then skipWindows wins' st' else st where wins' = S.delete t wins st' = shiftOne st layouts = ED.ewmhDesktopsLayout $ MD.avoidStruts -- make space for Gnome panels $ NB.smartBorders -- no border for the only window on screen ( Tall 1 (3/100) (1/2) ||| TC.ThreeCol 1 (3/100) (1/2) ||| Sliced 2 Nothing [] ||| Full) nextWS x = x CWS.Next CWS.HiddenNonEmptyWS prevWS x = x CWS.Prev CWS.HiddenNonEmptyWS emptyWS x = x CWS.Next CWS.EmptyWS myKeys x = -- Go to next/prev workspace. [ ((modMask x, xK_v), nextWS CWS.moveTo) , ((modMask x, xK_o), CWS.swapNextScreen) , ((modMask x, xK_k), prevWS CWS.moveTo) -- Move focus and window to next/prev workspace. , ((modMask x .|. shiftMask, xK_v), (nextWS CWS.shiftTo) >> (nextWS CWS.moveTo)) , ((modMask x .|. shiftMask, xK_o), CWS.shiftNextScreen >> CWS.swapNextScreen) , ((modMask x .|. shiftMask, xK_k), (prevWS CWS.shiftTo) >> (prevWS CWS.moveTo)) -- Move focus to other Xinerama screen. , ((modMask x .|. controlMask, xK_o), CWS.nextScreen) -- Move focus and window to other Xinerama screen. , ((modMask x .|. controlMask .|. shiftMask, xK_o), CWS.shiftNextScreen >> CWS.nextScreen) -- Get an empty workspace. , ((modMask x, xK_z), emptyWS CWS.moveTo) , ((modMask x .|. shiftMask, xK_z), (emptyWS CWS.shiftTo) >> (emptyWS CWS.moveTo)) , ((modMask x, xK_BackSpace), focusNextUnmapped) ] myManageHook = composeAll . concat $ [[ className =? c --> doFloat | c <- [ "Git-gui" , "Gitk" , "Skype.real" , "Update-manager"]]] main = do let c1 = CG.gnomeConfig { modMask = mod4Mask , layoutHook = layouts , manageHook = manageHook CG.gnomeConfig <+> myManageHook , keys = \x -> M.union (M.fromList (myKeys x)) (keys CG.gnomeConfig x) , focusFollowsMouse = False , borderWidth = 2 } c2 <- WN.withWindowNavigation (xK_Up, xK_Left, xK_Down, xK_Right) c1 xmonad c2