X-Git-Url: https://code.delx.au/dotfiles/blobdiff_plain/56e400ab5f7a7a60c7414207c8428fcca180f86b..6d3a69f07ef988ec7ba36b5ebd95ef69b54bfd50:/.xmonad/xmonad.hs diff --git a/.xmonad/xmonad.hs b/.xmonad/xmonad.hs index a9550a8..7fa7a65 100644 --- a/.xmonad/xmonad.hs +++ b/.xmonad/xmonad.hs @@ -1,12 +1,14 @@ +{-# LANGUAGE FlexibleContexts #-} import System.IO import XMonad +import XMonad.Actions.CycleRecentWS import XMonad.Actions.PhysicalScreens +import XMonad.Config.Desktop import XMonad.Hooks.DynamicLog import XMonad.Hooks.EwmhDesktops import XMonad.Hooks.ICCCMFocus import XMonad.Hooks.ManageDocks import XMonad.Hooks.ManageHelpers -import XMonad.Hooks.Script import XMonad.Hooks.SetWMName import XMonad.Layout.IM import XMonad.Layout.LayoutHints @@ -18,9 +20,7 @@ import XMonad.Layout.PerWorkspace import XMonad.Layout.Renamed import XMonad.Layout.Reflect import XMonad.Layout.Tabbed -import XMonad.Layout.ThreeColumns import XMonad.Util.Run(spawnPipe) -import XMonad.Util.WindowProperties(getProp32s) import qualified Data.Map as M import qualified XMonad.StackSet as W @@ -29,15 +29,16 @@ myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $ [ ((modm .|. shiftMask, xK_h), spawn "xfce4-session-logout"), ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command --lock"), + ((modm .|. shiftMask, xK_r), spawn "xmonad --restart"), ((modm, xK_n), spawn "xfce4-terminal"), ((modm, xK_i), spawn "firefox"), + ((modm, xK_c), spawn "emacsclient --create-frame --no-wait"), ((modm, xK_p), spawn "kupfer"), ((modm .|. shiftMask, xK_c ), kill), ((modm, xK_space ), sendMessage NextLayout), ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf), - ((modm, xK_Tab ), windows W.focusDown), ((modm, xK_j ), windows W.focusDown), ((modm, xK_k ), windows W.focusUp ), ((modm, xK_m ), windows W.focusMaster ), @@ -50,12 +51,13 @@ myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $ ((modm , xK_comma ), sendMessage (IncMasterN 1)), ((modm , xK_period), sendMessage (IncMasterN (-1))), ((modm , xK_b ), sendMessage ToggleStruts), - ((modm , xK_z ), sendMessage Mag.Toggle) + ((modm , xK_z ), sendMessage Mag.Toggle), + ((modm , xK_a), cycleRecentWS [xK_Super_L] xK_a xK_a) ] ++ - -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3 - -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3 + -- mod-{o,e,u}, Switch to physical/Xinerama screens 1, 2, or 3 + -- mod-shift-{o,e,u}, Move client to screen 1, 2, or 3 [((m .|. modm, key), f sc) | (key, sc) <- zip [xK_o, xK_e, xK_u] [0..] , (f, m) <- [(viewScreen, 0), (sendToScreen, shiftMask)] @@ -74,23 +76,14 @@ avoidMaster = W.modify' $ \c -> case c of W.Stack t [] (r:rs) -> W.Stack t [r] rs otherwise -> c -isTransient = ask >>= \w -> liftX $ do - r <- getProp32s "WM_TRANSIENT_FOR" w - return $ case r of - Just [_] -> True - _ -> False - isSkipTaskBar = isInProperty "_NET_WM_STATE" "_NET_WM_STATE_SKIP_TASKBAR" - myManageHook = manageDocks <+> composeOne [ - (className =? "Kupfer.py" <&&> resource =? "kupfer.py") -?> doFloat, - (className =? "Xfce4-appfinder" <&&> resource =? "xfce4-appfinder") -?> doFloatAt 0.1 0.1, + transience, (isSkipTaskBar -?> doFloat), (isDialog -?> doFloatAt 0.1 0.1), - (isTransient -?> doFloatAt 0.1 0.1), (isFullscreen -?> doFullFloat), (fmap Just $ doF avoidMaster) ] @@ -104,20 +97,19 @@ myPP = xmobarPP ppTitle = xmobarColor "#10A010" "" } -myLogHook h1 h2 = - dynamicLogWithPP myPP { ppOutput = hPutStrLn h1 } >> - dynamicLogWithPP myPP { ppOutput = hPutStrLn h2 } >> +myLogHook hooks = do + mapM (\h -> dynamicLogWithPP myPP { ppOutput = hPutStrLn h }) hooks takeTopFocus -- fix for Java Swing apps -myStartupHook = +myStartupHook = do setWMName "LG3D" -- fix for Java Swing apps - + spawn "xfce4-panel --restart" -- ensure it appears on top of xmobar goldenRatio = (toRational (2/(1+sqrt(5)::Double))) myTitleTheme = defaultTheme { fontName = "xft:sans-serif:size=10", - decoHeight = 22 + decoHeight = 24 } createLayout name layout = @@ -127,6 +119,7 @@ createLayout name layout = layout myFullLayout = createLayout "Full" $ + noBorders $ Full myTiledLayout = createLayout "Tall" $ @@ -142,15 +135,6 @@ myTabbedLayout = createLayout "Tab" $ avoidStruts $ tabbed shrinkText myTitleTheme -myThreeColLayout = createLayout "ThreeCol" $ - avoidStruts $ - Mag.magnifierOff $ - ThreeCol numMaster resizeDelta masterRatio - where - resizeDelta = 3/100 - masterRatio = 4/10 - numMaster = 1 - myMasterTabbedLayout = createLayout "MTab" $ avoidStruts $ Mag.magnifierOff $ @@ -168,36 +152,24 @@ myGimpLayout = createLayout "Gimp" $ reflectHoriz $ tabbed shrinkText myTitleTheme - --- This was the easiest way I found to avoid a compile error when I have --- an unused layout -referenceAllLayoutsToAvoidErrors = - myFullLayout ||| - myTiledLayout ||| - myTabbedLayout ||| - myThreeColLayout ||| - myMasterTabbedLayout ||| - myGimpLayout - - myLayout = ( - onWorkspace "1" (myTabbedLayout ||| myMasterTabbedLayout) $ - onWorkspace "2" (myTabbedLayout ||| myMasterTabbedLayout) $ - onWorkspace "9" (myFullLayout ||| myMasterTabbedLayout ||| myTabbedLayout ||| myTiledLayout ||| myGimpLayout) $ - (myMasterTabbedLayout ||| myTabbedLayout ||| myTiledLayout) + onWorkspace "9" (myTabbedLayout ||| myFullLayout ||| myGimpLayout) $ + (myTabbedLayout ||| myMasterTabbedLayout ||| myTiledLayout) ) main = do xmonadDir <- getXMonadDir - xmobar <- spawnPipe ("xmobar " ++ xmonadDir ++ "/xmobar.hs") - xmobar2 <- spawnPipe ("xmobar -x 1 " ++ xmonadDir ++ "/xmobar.hs") - xmonad $ ewmh defaultConfig { + xmobars <- mapM (\x -> spawnPipe ("xmobar -x " ++ (show x) ++ " " ++ xmonadDir ++ "/xmobar.hs")) [1, 2] + xmonad $ desktopConfig { manageHook = myManageHook, layoutHook = myLayout, workspaces = myWorkspaces, - logHook = myLogHook xmobar xmobar2, + logHook = myLogHook xmobars, startupHook = myStartupHook, - keys = myKeys + keys = myKeys, + modMask = mod4Mask, + handleEventHook = handleEventHook desktopConfig <+> fullscreenEventHook, + focusFollowsMouse = False }