{-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS -fno-warn-missing-signatures #-} ---------------------------------------------------------------------------- -- | -- Module : Config -- Copyright : (c) Jan Vornberger 2009 -- License : BSD3-style (see LICENSE) -- -- Maintainer : jan.vornberger@informatik.uni-oldenburg.de -- Stability : unstable -- Portability : not portable -- -- This module builds an XMonad configuration from Bluetile's configuration -- ----------------------------------------------------------------------------- module Config ( createXMonadConfig ) where import XMonad hiding ( (|||) ) import XMonad.Layout.BorderResize import XMonad.Layout.BoringWindows import XMonad.Layout.ButtonDecoration import XMonad.Layout.Decoration import XMonad.Layout.DecorationAddons import XMonad.Layout.DraggingVisualizer import XMonad.Layout.LayoutCombinators import XMonad.Layout.Maximize import XMonad.Layout.Minimize import XMonad.Layout.MouseResizableTile import XMonad.Layout.Named import XMonad.Layout.NoBorders import XMonad.Layout.PositionStoreFloat import XMonad.Layout.WindowSwitcherDecoration import XMonad.Actions.BluetileCommands import XMonad.Actions.CycleWS import XMonad.Actions.WindowMenu import XMonad.Hooks.CurrentWorkspaceOnTop import XMonad.Hooks.EwmhDesktops import XMonad.Hooks.ManageDocks import XMonad.Hooks.ManageHelpers import XMonad.Hooks.PositionStoreHooks import XMonad.Hooks.Minimize import XMonad.Hooks.ServerMode import XMonad.Hooks.SetWMName import XMonad.Hooks.WorkspaceByPos import XMonad.Config.Gnome import qualified XMonad.StackSet as W import qualified Data.Map as M import System.Exit import Data.Monoid import Control.Monad(when) import ConfigParser bluetileWorkspaces :: [String] bluetileWorkspaces = ["1","2","3","4","5","6","7","8","9","0"] bluetileKeys :: BluetileRC -> XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) bluetileKeys bluetilerc conf = M.fromList $ map (\(desc, action) -> (getKeyBinding desc bluetilerc, action)) $ -- launching and killing programs [ ("key_launch_terminal" , spawn $ XMonad.terminal conf) -- %! Launch terminal , ("key_gnome_run" , gnomeRun) -- %! Launch Gnome "Run application" dialog , ("key_close_window" , kill) -- %! Close the focused window , ("key_refresh" , refresh) -- %! Resize viewed windows to the correct size , ("key_reset_layouts" , setLayout $ XMonad.layoutHook conf) -- %! Reset the layouts on the current workspace to default , ("key_window_menu" , windowMenu) -- move focus up or down the window stack , ("key_focus_next_window" , focusDown) -- %! Move focus to the next window , ("key_focus_prev_window" , focusUp) -- %! Move focus to the previous window , ("key_focus_next_window_alternative" , focusDown) -- %! Move focus to the next window , ("key_focus_prev_window_alternative" , focusUp) -- %! Move focus to the previous window , ("key_focus_master_window" , focusMaster) -- %! Move focus to the master window -- modifying the window order , ("key_swap_with_master_window" , windows W.swapMaster) -- %! Swap the focused window and the master window , ("key_swap_with_next_window" , windows W.swapDown ) -- %! Swap the focused window with the next window , ("key_swap_with_prev_window" , windows W.swapUp ) -- %! Swap the focused window with the previous window -- resizing the master/slave ratio , ("key_shrink_master_area" , sendMessage Shrink) -- %! Shrink the master area , ("key_expand_master_area" , sendMessage Expand) -- %! Expand the master area , ("key_shrink_slave_area" , sendMessage ShrinkSlave) -- %! Shrink a slave area , ("key_expand_slave_area" , sendMessage ExpandSlave) -- %! Expand a slave area -- floating layer support , ("key_treat_as_regular_window" , withFocused $ windows . W.sink) -- %! Push window back into tiling , ("key_treat_as_dialog_window" , withFocused $ float ) -- %! Float window -- increase or decrease number of windows in the master area , ("key_inc_windows_in_master_area" , sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area , ("key_dec_windows_in_master_area" , sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area -- quit, or restart , ("key_quit_bluetile" , io (exitWith ExitSuccess)) -- %! Quit bluetile , ("key_restart_bluetile" , spawn "bluetile --restart") -- %! Restart bluetile -- Metacity-like workspace switching , ("key_prev_workspace" , prevWS) , ("key_next_workspace" , nextWS) , ("key_shift_window_to_prev_workspace" , shiftToPrev >> prevWS) , ("key_shift_window_to_next_workspace" , shiftToNext >> nextWS) -- more Metacity keys , ("key_gnome_run_alternative" , gnomeRun) , ("key_close_window_alternative" , kill) -- switching to layouts , ("key_switch_to_layout_stacked" , sendMessage $ JumpToLayout "Floating") , ("key_switch_to_layout_tiled1" , sendMessage $ JumpToLayout "Tiled1") , ("key_switch_to_layout_tiled2" , sendMessage $ JumpToLayout "Tiled2") , ("key_switch_to_layout_fullscreen" , sendMessage $ JumpToLayout "Fullscreen") -- maximizing and minimizing , ("key_maximize_window" , withFocused (sendMessage . maximizeRestore)) , ("key_minimize_window" , withFocused minimizeWindow) , ("key_restore_minimized_window" , sendMessage RestoreNextMinimizedWin) ] ++ -- mod-[1..9] ++ [0] %! Switch to workspace N [("key_switch_to_workspace_" ++ (show wkspNr), windows $ W.greedyView i) | (wkspNr :: Integer, i) <- zip ([1 .. 9] ++ [0]) (XMonad.workspaces conf)] ++ -- mod-shift-[1..9] ++ [0] %! Move client to workspace N [("key_shift_window_to_workspace_" ++ (show wkspNr), windows $ W.shift i) | (wkspNr :: Integer, i) <- zip ([1 .. 9] ++ [0]) (XMonad.workspaces conf)] ++ -- mod-{w,e,r} %! Switch to physical/Xinerama screens 1, 2, or 3 [("key_switch_to_screen_" ++ (show screenNr), screenWorkspace sc >>= flip whenJust (windows . W.view)) | (screenNr :: Integer, sc) <- zip [0 .. 2] [0 ..]] -- mod-shift-{w,e,r} %! Move client to screen 1, 2, or 3 ++ [("key_shift_window_to_screen_" ++ (show screenNr), screenWorkspace sc >>= flip whenJust (windows . W.shift)) | (screenNr :: Integer, sc) <- zip [0 .. 2] [0 ..]] bluetileMouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ()) bluetileMouseBindings (XConfig {XMonad.modMask = modMask'}) = M.fromList $ -- mod-button1 %! Move a floated window by dragging [ ((modMask', button1), (\w -> isFloating w >>= \isF -> when (isF) $ focus w >> mouseMoveWindow w >> windows W.shiftMaster)) -- mod-button2 %! Switch to next and first layout , ((modMask', button2), (\_ -> sendMessage NextLayout)) , ((modMask' .|. shiftMask, button2), (\_ -> sendMessage $ JumpToLayout "Floating")) -- mod-button3 %! Resize a floated window by dragging , ((modMask', button3), (\w -> isFloating w >>= \isF -> when (isF) $ focus w >> mouseResizeWindow w >> windows W.shiftMaster)) ] isFloating :: Window -> X (Bool) isFloating w = do ws <- gets windowset return $ M.member w (W.floating ws) bluetileManageHook :: ManageHook bluetileManageHook = composeAll [ workspaceByPos, positionStoreManageHook (Just defaultThemeWithButtons) , className =? "MPlayer" --> doFloat , isFullscreen --> doFullFloat , manageDocks] bluetileLayoutHook bluetileTheme = avoidStruts $ minimize $ boringWindows $ ( named "Floating" floating ||| named "Tiled1" tiled1 ||| named "Tiled2" tiled2 ||| named "Fullscreen" fullscreen ) where floating = floatingDeco $ maximize $ borderResize $ positionStoreFloat tiled1 = tilingDeco $ maximize $ mouseResizableTile { isMirrored = True } tiled2 = tilingDeco $ maximize $ mouseResizableTile fullscreen = tilingDeco $ maximize $ smartBorders Full tilingDeco l = windowSwitcherDecorationWithButtons shrinkText bluetileTheme (draggingVisualizer l) floatingDeco l = buttonDeco shrinkText bluetileTheme l createXMonadConfig bluetilerc = defaultConfig { modMask = defaultModifierBRC bluetilerc, startupHook = ewmhDesktopsStartup >> setWMName "LG3D", manageHook = bluetileManageHook, layoutHook = bluetileLayoutHook bluetileTheme, logHook = currentWorkspaceOnTop >> ewmhDesktopsLogHook, handleEventHook = ewmhDesktopsEventHook `mappend` fullscreenEventHook `mappend` minimizeEventHook `mappend` serverModeEventHook' bluetileCommands `mappend` positionStoreEventHook, workspaces = bluetileWorkspaces, keys = bluetileKeys bluetilerc, mouseBindings = bluetileMouseBindings, focusFollowsMouse = focusFollowsMouseBRC bluetilerc, normalBorderColor = getDecoConfig "window_border_normal_color" bluetilerc, focusedBorderColor = getDecoConfig "window_border_focused_color" bluetilerc, terminal = terminalBRC bluetilerc } where bluetileTheme = defaultThemeWithButtons { activeColor = getDecoConfig "decoration_focused_color" bluetilerc , activeTextColor = getDecoConfig "decoration_focused_text_color" bluetilerc , activeBorderColor = getDecoConfig "decoration_focused_border_color" bluetilerc , inactiveColor = getDecoConfig "decoration_normal_color" bluetilerc , inactiveTextColor = getDecoConfig "decoration_normal_text_color" bluetilerc , inactiveBorderColor = getDecoConfig "decoration_normal_border_color" bluetilerc , fontName = getDecoConfig "decoration_font" bluetilerc } getDecoConfig :: String -> BluetileRC -> String getDecoConfig desc bluetilerc = case (lookup desc (decorationBRC bluetilerc)) of (Just decoConfig) -> decoConfig (Nothing) -> error $ "Configuration does not include decoration config value for '" ++ desc ++ "'" getKeyBinding :: String -> BluetileRC -> (KeyMask, KeySym) getKeyBinding desc bluetilerc = case (lookup desc (keysBRC bluetilerc)) of (Just keybinding) -> keybinding (Nothing) -> error $ "Configuration does not include key binding for key '" ++ desc ++ "'"