{-# 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 -- -- The default configuration of bluetile -- ----------------------------------------------------------------------------- module Config where import XMonad hiding ( (|||) ) import XMonad.Layout hiding ( (|||) ) import XMonad.Layout.Maximize import XMonad.Layout.Minimize import XMonad.Layout.NoBorders import XMonad.Layout.LayoutCombinators import XMonad.Layout.Named import XMonad.Layout.BoringWindows import XMonad.Layout.Decoration import XMonad.Layout.WindowSwitcherDecoration import XMonad.Layout.DraggingVisualizer import XMonad.Layout.PositionStoreFloat import XMonad.Layout.BorderResize import XMonad.Layout.MouseResizableTile import XMonad.Layout.NoFrillsDecoration import XMonad.Actions.CycleWS import XMonad.Actions.BluetileCommands import XMonad.Actions.WindowMenu import XMonad.Hooks.ManageDocks import XMonad.Hooks.EwmhDesktops import XMonad.Hooks.CustomRestart import XMonad.Hooks.RestoreMinimized import XMonad.Hooks.WorkspaceByPos import XMonad.Hooks.BluetileDock import XMonad.Hooks.ServerMode 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) blueTileWorkspaces :: [String] blueTileWorkspaces = ["1","2","3","4","5","6","7","8","9","0"] blueTileKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) blueTileKeys conf@(XConfig {XMonad.modMask = modMask'}) = M.fromList $ -- launching and killing programs [ ((modMask' , xK_Return), spawn $ XMonad.terminal conf) -- %! Launch terminal , ((modMask', xK_p ), gnomeRun) -- %! Launch Gnome "Run application" dialog , ((modMask' .|. shiftMask, xK_c ), kill) -- %! Close the focused window , ((modMask', xK_F5 ), refresh) -- %! Resize viewed windows to the correct size , ((modMask' .|. shiftMask, xK_F5 ), setLayout $ XMonad.layoutHook conf) -- %! Reset the layouts on the current workspace to default , ((modMask', xK_o ), windowMenu) -- move focus up or down the window stack , ((modMask', xK_Tab ), focusDown) -- %! Move focus to the next window , ((modMask' .|. shiftMask, xK_Tab ), focusUp) -- %! Move focus to the previous window , ((modMask', xK_j ), focusDown) -- %! Move focus to the next window , ((modMask', xK_k ), focusUp) -- %! Move focus to the previous window -- modifying the window order , ((modMask' .|. shiftMask, xK_j ), windows W.swapDown ) -- %! Swap the focused window with the next window , ((modMask' .|. shiftMask, xK_k ), windows W.swapUp ) -- %! Swap the focused window with the previous window -- resizing the master/slave ratio , ((modMask', xK_h ), sendMessage Shrink) -- %! Shrink the master area , ((modMask', xK_l ), sendMessage Expand) -- %! Expand the master area , ((modMask', xK_u ), sendMessage ShrinkSlave) -- %! Shrink a slave area , ((modMask', xK_i ), sendMessage ExpandSlave) -- %! Expand a slave area -- floating layer support , ((modMask', xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling , ((modMask' .|. shiftMask, xK_t ), withFocused $ float ) -- %! Float window -- increase or decrease number of windows in the master area , ((modMask' , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area , ((modMask' , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area -- quit, or restart , ((modMask' .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit bluetile , ((modMask' , xK_q ), spawn "bluetile --restart") -- %! Restart bluetile -- Metacity-like workspace switching , ((mod1Mask .|. controlMask, xK_Left), prevWS) , ((mod1Mask .|. controlMask, xK_Right), nextWS) , ((mod1Mask .|. controlMask .|. shiftMask, xK_Left), shiftToPrev >> prevWS) , ((mod1Mask .|. controlMask .|. shiftMask, xK_Right), shiftToNext >> nextWS) -- more Metacity keys , ((mod1Mask , xK_F2), gnomeRun) , ((mod1Mask , xK_F4), kill) -- Switching to layouts , ((modMask' , xK_a), sendMessage $ JumpToLayout "Floating") , ((modMask' , xK_s), sendMessage $ JumpToLayout "Tiled1") , ((modMask' , xK_d), sendMessage $ JumpToLayout "Tiled2") , ((modMask' , xK_f), sendMessage $ JumpToLayout "Fullscreen") -- Maximizing , ((modMask' , xK_z), withFocused (sendMessage . maximizeRestore)) -- Minimizing , ((modMask', xK_m ), withFocused (\f -> sendMessage (MinimizeWin f))) , ((modMask' .|. shiftMask, xK_m ), sendMessage RestoreNextMinimizedWin) ] ++ -- mod-[1..9] ++ [0] %! Switch to workspace N -- mod-shift-[1..9] ++ [0] %! Move client to workspace N [((m .|. modMask', k), windows $ f i) | (i, k) <- zip (XMonad.workspaces conf) ([xK_1 .. xK_9] ++ [xK_0]) , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]] ++ -- 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 [((m .|. modMask', key), screenWorkspace sc >>= flip whenJust (windows . f)) | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..] , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]] 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 , className =? "MPlayer" --> doFloat , manageDocks] blueTileLayoutHook = avoidStruts $ boringAuto $ minimize $ ( named "Floating" floating ||| named "Tiled1" tiled1 ||| named "Tiled2" tiled2 ||| named "Fullscreen" fullscreen ) where floating = floatingDeco $ maximize $ borderResize $ positionStoreFloat tiled1 = tilingDeco $ maximize $ mouseResizableTileMirrored tiled2 = tilingDeco $ maximize $ mouseResizableTile fullscreen = tilingDeco $ maximize $ smartBorders Full tilingDeco l = windowSwitcherDecoration shrinkText defaultTheme (draggingVisualizer l) floatingDeco l = noFrillsDeco shrinkText defaultTheme l blueTileConfig dockHandle = defaultConfig { modMask = mod4Mask, -- logo key manageHook = blueTileManageHook, layoutHook = blueTileLayoutHook, logHook = ewmhDesktopsLogHook >> bluetileDock dockHandle, handleEventHook = ewmhDesktopsEventHook `mappend` customRestartEventHook "bluetile" `mappend` restoreMinimizedEventHook `mappend` serverModeEventHookCustom bluetileCommands, workspaces = blueTileWorkspaces, keys = blueTileKeys, mouseBindings = blueTileMouseBindings, focusFollowsMouse = False, focusedBorderColor = "#ff5500", terminal = "gnome-terminal" }