Difference between revisions of "Xmonad/Config archive/loupgaroublonds xmonad.hs"

From HaskellWiki
Jump to navigation Jump to search
m (Xmonad/Config archive/loupgaroublond's xmonad.hs moved to Xmonad/Config archive/loupgaroublonds xmonad.hs)
(much updated config)
Line 1: Line 1:
 
<haskell>
 
<haskell>
  +
{-# OPTIONS_GHC -fglasgow-exts #-}
  +
 
import XMonad
 
import XMonad
import System.Exit
+
import XMonad.Operations
  +
 
import qualified XMonad.StackSet as W
+
import XMonad.Actions.Commands
import qualified Data.Map as M
+
import XMonad.Actions.CycleWS
  +
import XMonad.Actions.DeManage
  +
 
import XMonad.Hooks.EwmhDesktops
 
import XMonad.Hooks.EwmhDesktops
 
import XMonad.Hooks.ManageDocks
 
import XMonad.Hooks.ManageDocks
  +
import XMonad.Hooks.ManageHelpers
   
main = xmonad $ defaultConfig
 
{ borderWidth = 3
 
, terminal = "gnome-terminal"
 
, defaultGaps = _defaultGaps
 
, normalBorderColor = _normalBorderColor
 
, focusedBorderColor = _focusedBorderColor
 
 
, layoutHook = _layout
 
, keys = _keys
 
, manageHook = _manageHook
 
, logHook = _logHook }
 
   
  +
import qualified XMonad.Util.EZConfig as EZ
_defaultGaps = [(0,0,0,0)]
 
  +
import XMonad.Util.Run
  +
import XMonad.Util.WindowProperties
  +
import XMonad.Util.XSelection
   
  +
import qualified Data.Map as M
_normalBorderColor = "#e7e7e7"
 
_focusedBorderColor = "#AFD6ED"
 
   
  +
import qualified XMonad.Actions.DwmPromote as DwmP
_keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
 
  +
import qualified XMonad.Actions.FlexibleResize as Flex
-- launch a terminal
 
  +
import qualified XMonad.Actions.SinkAll as SinkAll
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
 
  +
-- launch dmenu
 
  +
import qualified XMonad.Layout.PerWorkspace as PW
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
 
  +
import qualified XMonad.Layout.Tabbed as Tab
-- launch gmrun
 
  +
, ((modMask .|. shiftMask, xK_p ), spawn "gmrun")
 
  +
import qualified XMonad.StackSet as W
-- close focused window
 
  +
, ((modMask .|. shiftMask, xK_c ), kill)
 
  +
import Data.Monoid
-- Rotate through the available layout algorithms
 
  +
import Data.Maybe
, ((modMask, xK_space ), sendMessage NextLayout)
 
  +
import System.IO
-- Reset the layouts on the current workspace to default
 
  +
import System.Exit
, ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
 
  +
-- Resize viewed windows to the correct size
 
  +
main = do
, ((modMask, xK_n ), refresh)
 
  +
xmonad $ _config
-- Move focus to the next window
 
  +
, ((modMask, xK_Tab ), windows W.focusDown)
 
  +
_config = defaultConfig
-- Move focus to the next window
 
, ((modMask, xK_j ), windows W.focusDown)
+
{ borderWidth = 2
  +
, terminal = terminalCmd
-- Move focus to the previous window
 
  +
, normalBorderColor = _normalBorderColor
, ((modMask, xK_k ), windows W.focusUp )
 
  +
, focusedBorderColor = _focusedBorderColor
-- Move focus to the master window
 
, ((modMask, xK_m ), windows W.focusMaster )
+
, workspaces = ["werk", "web", "praten", "muziek"
  +
, "bier", "zes", "zeven", "acht"
-- Swap the focused window and the master window
 
, ((modMask, xK_Return), windows W.swapMaster)
+
, "negen", "tien"]
  +
, layoutHook = _layout
-- Swap the focused window with the next window
 
, ((modMask .|. shiftMask, xK_j ), windows W.swapDown )
+
, keys = _keys
-- Swap the focused window with the previous window
+
, modMask = mod4Mask
  +
, logHook = _logHook
, ((modMask .|. shiftMask, xK_k ), windows W.swapUp )
 
  +
, manageHook = _manageHook }
-- Shrink the master area
 
  +
, ((modMask, xK_h ), sendMessage Shrink)
 
  +
-- Expand the master area
 
  +
_normalBorderColor :: String
, ((modMask, xK_l ), sendMessage Expand)
 
  +
_normalBorderColor = "#EFEFEF"
-- Push window back into tiling
 
  +
, ((modMask, xK_t ), withFocused $ windows . W.sink)
 
  +
_focusedBorderColor :: String
-- Increment the number of windows in the master area
 
  +
_focusedBorderColor= "#000000"
, ((modMask , xK_comma ), sendMessage (IncMasterN 1))
 
  +
-- Deincrement the number of windows in the master area
 
  +
-- Applications
, ((modMask , xK_period), sendMessage (IncMasterN (-1)))
 
  +
terminalCmd :: String
-- toggle the status bar gap
 
  +
terminalCmd = "gnome-terminal"
, ((modMask , xK_b ),
 
  +
modifyGap (\i n -> let x = (XMonad.defaultGaps conf ++ repeat (0,0,0,0)) !! i
 
  +
runTerminal :: X ()
in if n == x then (0,0,0,0) else x))
 
  +
runTerminal = spawn terminalCmd
-- Quit xmonad
 
  +
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
 
  +
saveSession :: String -> String
-- Restart xmonad
 
  +
saveSession cmd = "bash -c '" ++ cmd ++ "; bash'"
, ((modMask , xK_q ),
 
  +
pasteTerminal :: X ()
broadcastMessage ReleaseResources >> restart (Just "xmonad") True)
 
  +
pasteTerminal = modifySelectionAndUnsafePromptSelection saveSession $ terminalCmd ++ " -x "
]
 
  +
++
 
  +
browserCmd :: String
--
 
  +
browserCmd = "firefox"
-- mod-[1..9], Switch to workspace N
 
  +
-- mod-shift-[1..9], Move client to workspace N
 
  +
runBrowser :: X ()
--
 
  +
runBrowser = spawn browserCmd
[((m .|. modMask, k), windows $ f i)
 
  +
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
 
  +
pasteBrowser :: X ()
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
 
  +
pasteBrowser = safePromptSelection browserCmd
++
 
  +
--
 
  +
cmdLineCmd :: String
-- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
 
  +
cmdLineCmd = "gmrun"
-- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
 
  +
--
 
  +
runCmdLine :: X ()
[((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
 
  +
runCmdLine = spawn cmdLineCmd
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
 
  +
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
 
  +
fileManagerCmd :: String
 
  +
fileManagerCmd = "nautilus"
------------------------------------------------------------------------
 
  +
-- Mouse bindings: default actions bound to mouse events
 
  +
runFileManager :: X ()
--
 
  +
runFileManager = spawn fileManagerCmd
  +
  +
musicPlayerCmd :: String
  +
musicPlayerCmd = "exaile"
  +
  +
runMusicPlayer :: X ()
  +
runMusicPlayer = spawn musicPlayerCmd
  +
  +
pasteMusicPlayer :: X ()
  +
pasteMusicPlayer = promptSelection musicPlayerCmd
  +
  +
  +
-- Keys
  +
_keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X())
  +
_keys = \conf -> EZ.mkKeymap conf $(_emacsKeys conf)
  +
  +
_emacsKeys :: XConfig Layout -> [(String, X())]
  +
_emacsKeys = \conf ->
  +
[ -- Applications
  +
("M-t", runTerminal)
  +
, ("M-v M-t", pasteTerminal)
  +
, ("M-i", runBrowser)
  +
, ("M-v M-i", pasteBrowser)
  +
, ("M-p", runCmdLine)
  +
, ("M-e", runMusicPlayer)
  +
, ("M-h", runFileManager)
  +
  +
-- Layouts
  +
, ("M-n", refresh)
  +
, ("M-S-<Space>", setLayout $ XMonad.layoutHook conf)
  +
, ("M-<Space>", sendMessage NextLayout)
  +
, ("M-<Tab>", windows W.focusDown)
  +
, ("M-j", windows W.focusDown)
  +
, ("M-k", windows W.focusUp)
  +
, ("M-<Return>", windows W.focusMaster)
  +
, ("M-S-<Return>", DwmP.dwmpromote)
  +
, ("M-S-j", windows W.swapDown)
  +
, ("M-S-k", windows W.swapUp)
  +
, ("M-g", sendMessage Shrink)
  +
, ("M-l", sendMessage Expand)
  +
, ("M-r", withFocused $ windows . W.sink)
  +
, ("M-,", sendMessage (IncMasterN 1))
  +
, ("M-.", sendMessage (IncMasterN (-1)))
  +
-- Toggle full screen
  +
, ("M-<F12>", sendMessage ToggleStruts >> refresh)
  +
  +
-- Windows
  +
, ("M-c", kill) -- window
  +
, ("M-S-c", SinkAll.withAll killWindow) ] -- window
  +
++
  +
[ ("M-S-" ++ [num], windows $ W.shift name)
  +
| (name, num) <-
  +
zip (XMonad.workspaces conf) (['1' .. '9'] ++ ['0'])]
  +
  +
-- Workspaces
  +
++
  +
[ ("M-" ++ [num], windows $ W.greedyView name)
  +
| (name, num) <-
  +
zip (XMonad.workspaces conf) (['1' .. '9'] ++ ['0'])]
  +
++
  +
[ ("M-<Right>", moveTo Next NonEmptyWS)
  +
, ("M-<Left>", moveTo Prev NonEmptyWS)
  +
, ("M-S-<Right>", moveTo Next EmptyWS)
  +
, ("M-S-<Left>", moveTo Prev EmptyWS)
  +
-- Toggle between current and previous
  +
, ("M-`", toggleWS)
  +
  +
-- xmonad
  +
, ("M1-q", broadcastMessage ReleaseResources
  +
>> restart "xmonad" True)]
  +
  +
  +
-- Mouse bindings
  +
  +
_mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
 
_mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
 
_mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
 
 
-- mod-button1, Set the window to floating mode and move by dragging
 
-- mod-button1, Set the window to floating mode and move by dragging
 
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
 
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
Line 101: Line 171:
 
, ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
 
, ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
 
-- mod-button3, Set the window to floating mode and resize by dragging
 
-- mod-button3, Set the window to floating mode and resize by dragging
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w))
+
, ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
 
]
 
]
  +
------------------------------------------------------------------------
 
-- Layouts:
+
-- Layouts
  +
 
  +
_layout = ewmhDesktopsLayout $ avoidStruts $ PW.onWorkspaces ["web", "bier"] Tab.simpleTabbed
-- You can specify and transform your layouts by modifying these values.
 
  +
(tiled ||| Mirror tiled ||| Tab.simpleTabbed)
-- If you change layout bindings be sure to use 'mod-shift-space' after
 
-- restarting (with 'mod-q') to reset your layout state to the new
 
-- defaults, as xmonad preserves your old layout settings by default.
 
--
 
-- The available layouts. Note that each layout is separated by |||,
 
-- which denotes layout choice.
 
--
 
_layout = avoidStruts (tiled ||| Mirror tiled ||| Full)
 
 
where
 
where
-- default tiling algorithm partitions the screen into two panes
 
 
tiled = Tall nmaster delta ratio
 
tiled = Tall nmaster delta ratio
-- The default number of windows in the master pane
 
 
nmaster = 1
 
nmaster = 1
-- Default proportion of screen occupied by master pane
 
 
ratio = 1/2
 
ratio = 1/2
-- Percent of screen to increment by when resizing panes
 
 
delta = 3/100
 
delta = 3/100
  +
 
  +
-- ManageHooks
------------------------------------------------------------------------
 
-- Window rules:
 
 
-- Execute arbitrary actions and WindowSet manipulations when managing
 
-- a new window. You can use this to, for example, always float a
 
-- particular program, or have a client always appear on a particular
 
-- workspace.
 
--
 
-- To find the property name associated with a program, use
 
-- > xprop | grep WM_CLASS
 
-- and click on the client you're interested in.
 
--
 
-- To match on the WM_NAME, you can use 'title' in the same way that
 
-- 'className' and 'resource' are used below.
 
--
 
 
_manageHook = composeAll
 
_manageHook = composeAll
[ className =? "MPlayer" --> doFloat
+
[ className =? "MPlayer" --> doFloat
, className =? "Gimp" --> doFloat
+
, resource =? "desktop_window" --> doIgnore
, resource =? "desktop_window" --> doIgnore
+
, className =? "Kplayer" --> doFloat
, resource =? "kdesktop" --> doIgnore ]
+
, className =? "Exaile.py" --> doF (W.shift "muziek")
  +
, className =? "Firstboot" --> doFloat
<+> manageDocks
 
  +
, className =? "CinePaint" --> doFloat
 
  +
, title =? "Follow-up Curves (Br2HDR)" --> doFloat
------------------------------------------------------------------------
 
  +
, className =? "Plasma" --> doIgnore
-- Status bars and logging
 
  +
, className =? "Qt-subapplication" --> doIgnore
 
  +
, checkDock --> doIgnore ]
-- Perform an arbitrary action on each internal state change or X event.
 
  +
<+> composeOne
-- See the 'DynamicLog' extension for examples.
 
  +
[ transience
--
 
  +
, className =? "Firefox" -?> doF (W.shift "web")
-- To emulate dwm's status bar
 
  +
]
--
 
  +
<+> manageDocks
-- > logHook = dynamicLogDzen
 
  +
--
 
  +
_logHook = do ewmhDesktopsLogHook
 
  +
-- LogHooks
return ()
 
  +
  +
_logHook = ewmhDesktopsLogHook
  +
 
</haskell>
 
</haskell>

Revision as of 01:25, 22 December 2008

{-# OPTIONS_GHC -fglasgow-exts #-}

import XMonad
import XMonad.Operations

import XMonad.Actions.Commands
import XMonad.Actions.CycleWS
import XMonad.Actions.DeManage

import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers


import qualified XMonad.Util.EZConfig as EZ
import XMonad.Util.Run
import XMonad.Util.WindowProperties
import XMonad.Util.XSelection

import qualified Data.Map as M

import qualified XMonad.Actions.DwmPromote as DwmP
import qualified XMonad.Actions.FlexibleResize as Flex
import qualified XMonad.Actions.SinkAll as SinkAll

import qualified XMonad.Layout.PerWorkspace as PW
import qualified XMonad.Layout.Tabbed as Tab

import qualified XMonad.StackSet as W

import Data.Monoid
import Data.Maybe
import System.IO
import System.Exit

main = do
  xmonad $ _config

_config = defaultConfig
          { borderWidth        = 2
          , terminal           = terminalCmd
          , normalBorderColor  = _normalBorderColor
          , focusedBorderColor = _focusedBorderColor
          , workspaces         = ["werk", "web", "praten", "muziek"
                                 , "bier", "zes", "zeven", "acht"
                                 , "negen", "tien"]
          , layoutHook = _layout
          , keys = _keys
          , modMask = mod4Mask
          , logHook = _logHook
          , manageHook = _manageHook }


_normalBorderColor :: String
_normalBorderColor = "#EFEFEF"

_focusedBorderColor :: String
_focusedBorderColor= "#000000"

-- Applications
terminalCmd :: String
terminalCmd = "gnome-terminal"

runTerminal :: X ()
runTerminal = spawn terminalCmd

saveSession :: String -> String
saveSession cmd = "bash -c '" ++ cmd ++ "; bash'"
pasteTerminal :: X ()
pasteTerminal = modifySelectionAndUnsafePromptSelection saveSession $ terminalCmd ++ " -x "

browserCmd :: String
browserCmd = "firefox"

runBrowser :: X ()
runBrowser = spawn browserCmd

pasteBrowser :: X ()
pasteBrowser = safePromptSelection browserCmd

cmdLineCmd :: String
cmdLineCmd = "gmrun"

runCmdLine :: X ()
runCmdLine = spawn cmdLineCmd

fileManagerCmd :: String
fileManagerCmd = "nautilus"

runFileManager :: X ()
runFileManager = spawn fileManagerCmd

musicPlayerCmd :: String
musicPlayerCmd = "exaile"

runMusicPlayer :: X ()
runMusicPlayer = spawn musicPlayerCmd

pasteMusicPlayer :: X ()
pasteMusicPlayer = promptSelection musicPlayerCmd


-- Keys
_keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X())
_keys = \conf -> EZ.mkKeymap conf $(_emacsKeys conf)

_emacsKeys :: XConfig Layout -> [(String, X())]
_emacsKeys  = \conf ->
              [ -- Applications
                ("M-t", runTerminal)
              , ("M-v M-t", pasteTerminal)
              , ("M-i", runBrowser)
              , ("M-v M-i", pasteBrowser)
              , ("M-p", runCmdLine)
              , ("M-e", runMusicPlayer)
              , ("M-h", runFileManager)

              -- Layouts
              , ("M-n", refresh)
              , ("M-S-<Space>", setLayout $ XMonad.layoutHook conf)
              , ("M-<Space>", sendMessage NextLayout)
              , ("M-<Tab>", windows W.focusDown)
              , ("M-j", windows W.focusDown)
              , ("M-k", windows W.focusUp)
              , ("M-<Return>", windows W.focusMaster)
              , ("M-S-<Return>",  DwmP.dwmpromote)
              , ("M-S-j", windows W.swapDown)
              , ("M-S-k", windows W.swapUp)
              , ("M-g", sendMessage Shrink)
              , ("M-l", sendMessage Expand)
              , ("M-r", withFocused $ windows . W.sink)
              , ("M-,", sendMessage (IncMasterN 1))
              , ("M-.", sendMessage (IncMasterN (-1)))
              -- Toggle full screen
              , ("M-<F12>", sendMessage ToggleStruts >> refresh)

              -- Windows
              , ("M-c", kill)             -- window
              , ("M-S-c", SinkAll.withAll killWindow) ] -- window
              ++
              [ ("M-S-" ++ [num], windows $ W.shift name)
                    | (name, num) <-
                        zip (XMonad.workspaces conf) (['1' .. '9'] ++ ['0'])]

              -- Workspaces
              ++
              [ ("M-" ++ [num], windows $ W.greedyView name)
                    | (name, num) <-
                        zip (XMonad.workspaces conf) (['1' .. '9'] ++ ['0'])]
              ++
              [ ("M-<Right>", moveTo Next NonEmptyWS)
              , ("M-<Left>", moveTo Prev NonEmptyWS)
              , ("M-S-<Right>", moveTo Next EmptyWS)
              , ("M-S-<Left>", moveTo Prev EmptyWS)
              -- Toggle between current and previous
              , ("M-`", toggleWS)

              -- xmonad
              , ("M1-q", broadcastMessage ReleaseResources
                           >> restart "xmonad" True)]


-- Mouse bindings

_mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
_mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
    -- mod-button1, Set the window to floating mode and move by dragging
    [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
    -- mod-button2, Raise the window to the top of the stack
    , ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
    -- mod-button3, Set the window to floating mode and resize by dragging
    , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
    -- you may also bind events to the mouse scroll wheel (button4 and button5)
    ]

-- Layouts

_layout = ewmhDesktopsLayout $ avoidStruts $ PW.onWorkspaces ["web", "bier"] Tab.simpleTabbed
          (tiled ||| Mirror tiled ||| Tab.simpleTabbed)
    where
      tiled   = Tall nmaster delta ratio
      nmaster = 1
      ratio   = 1/2
      delta   = 3/100

-- ManageHooks
_manageHook = composeAll
              [ className =? "MPlayer"        --> doFloat
              , resource  =? "desktop_window" --> doIgnore
              , className =? "Kplayer"        --> doFloat
              , className =? "Exaile.py"      --> doF (W.shift "muziek")
              , className =? "Firstboot"      --> doFloat
              , className =? "CinePaint"      --> doFloat
              , title =? "Follow-up Curves (Br2HDR)" --> doFloat
              , className =? "Plasma"         --> doIgnore
              , className =? "Qt-subapplication" --> doIgnore
              , checkDock --> doIgnore ] 
              <+> composeOne
                      [ transience
                      , className =? "Firefox"    -?> doF (W.shift "web")
                      ]
              <+> manageDocks


-- LogHooks

_logHook = ewmhDesktopsLogHook