You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
xmonad/xmonad.hs

123 lines
5.2 KiB

9 years ago
import XMonad
import XMonad.Actions.CycleWS
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
import XMonad.Util.Run(spawnPipe)
import XMonad.Util.EZConfig
import XMonad.Util.Scratchpad
import XMonad.Config.Desktop
import XMonad.Config.Azerty
import XMonad.Layout.Fullscreen
import XMonad.Layout.NoBorders
import XMonad.Layout.Maximize
import XMonad.Layout.Tabbed
import XMonad.Layout.Minimize
import XMonad.Layout.BoringWindows
import XMonad.Layout.PerWorkspace
import XMonad.Prompt
import XMonad.Prompt.Ssh
import System.IO
import qualified Data.Map as M
import qualified XMonad.StackSet as W
import qualified Data.List as L
baseConfig = desktopConfig
{ modMask = mod5Mask -- AltGr
, terminal = "mate-terminal.wrapper"
, workspaces = ["1:web", "2:com", "3:dev"] ++ map show [4..7] ++ ["8:media", "9:div"]
, layoutHook = smartBorders $ fullscreenFull $ avoidStruts $ boringWindows $ minimize $ maximize $ onWorkspace "8:media" Full $ onWorkspaces ["2:com", "9:div"] simpleTabbed $ (layoutHook desktopConfig ||| simpleTabbed )
9 years ago
, handleEventHook = handleEventHook desktopConfig <+> fullscreenEventHook
}
`removeKeys`
[(m .|. modMask baseConfig , k)
| (k) <- [xK_1 .. xK_9]
, (m) <- [(0), (shiftMask)]]
-- `removeKeys`
-- [(modMask baseConfig .|. shiftMask, xK_q)]
baseXPConfig = defaultXPConfig {
position = Top
}
workspaceManageHook :: ManageHook
workspaceManageHook = composeAll [
className =? "Firefox" --> doShift "1:web"
,className =? "Icedove" --> doShift "2:com"
,className =? "Gajim" --> doShift "2:com"
,className =? "jetbrains-phpstorm" --> doShift "3:dev"
,className =? "jetbrains-pycharm" --> doShift "3:dev"
,className =? "KeePass2" --> doShift "9:div"
,className =? "Xmessage" --> doFloat
,className =? "Clementine" --> doShift "8:media"
9 years ago
]
main = do
xmobar_proc <- spawnPipe "xmobar"
spawn "exec ~/.xmonad/action-manager/start.sh ~/.xmonad/actiondisplay ~/.xmonad/actioncontrol --state-file ~/.xmonad/actionstate --redshift-enabled --redshift-location 51:5 --redshift-temperature 6000:2000"
9 years ago
xmonad $ baseConfig
{ manageHook = (scratchpadManageHook $ W.RationalRect 0.0 0.0 1.0 0.5) <+> workspaceManageHook <+> fullscreenManageHook <+> manageDocks
9 years ago
, logHook = dynamicLogWithPP xmobarPP
{ ppOutput = hPutStrLn xmobar_proc
, ppTitle = xmobarColor "green" "" . shorten 50
, ppSort = fmap(.scratchpadFilterOutWorkspace) (ppSort xmobarPP)
, ppOrder = \(ws:_:t:_) -> [ws, t]
}
}
`additionalKeys`
[ ((modMask baseConfig .|. controlMask, xK_l), spawn "xscreensaver-command -lock")
, ((modMask baseConfig .|. controlMask, xK_s), spawn "systemctl hibernate")
, ((modMask baseConfig, xK_r), spawn "~/.xmonad/toggle-redshift.sh")
9 years ago
, ((modMask baseConfig, xK_e), spawn "caja")
, ((0, xK_Print), spawn "scrot")
-- Normal Alt-Tab behavior
, ((mod1Mask, xK_Tab ), windows W.focusDown) -- %! Move focus to the next window
, ((mod1Mask .|. shiftMask, xK_Tab ), windows W.focusUp ) -- %! Move focus to the previous window
-- XMonad.Actions.CycleWS
, ((modMask baseConfig, xK_Right), nextWS)
, ((modMask baseConfig, xK_Left), prevWS)
, ((modMask baseConfig .|. shiftMask, xK_Right), shiftToNext >> nextWS)
, ((modMask baseConfig .|. shiftMask, xK_Left), shiftToPrev >> prevWS)
-- XMonad.Layout.Maximize
, ((modMask baseConfig, xK_F11), withFocused (sendMessage . maximizeRestore))
-- XMonad.Prompt.Ssh
, ((modMask baseConfig, xK_s), sshPrompt baseXPConfig)
-- XMonad.Layout.Minimize
, ((modMask baseConfig, xK_c), withFocused minimizeWindow)
, ((modMask baseConfig, xK_g), sendMessage RestoreNextMinimizedWin)
-- XMonad.Layout.BoringWindows
, ((modMask baseConfig, xK_j), focusUp)
, ((modMask baseConfig, xK_k), focusDown)
, ((modMask baseConfig, xK_m), focusMaster)
-- XMonad.Util.Scratchpad
, ((modMask baseConfig, xK_F12), scratchpadSpawnActionCustom "mate-terminal --disable-factory --name scratchpad")
-- Azerty support
, ((modMask baseConfig, xK_semicolon), sendMessage (IncMasterN (-1)))
-- mute button
, ((0, 0x1008FF12), spawn "echo mt | ~/.xmonad/action-manager/command.sh ~/.xmonad/actioncontrol")
9 years ago
-- volumeup button
, ((0, 0x1008FF13), spawn "echo + | ~/.xmonad/action-manager/command.sh ~/.xmonad/actioncontrol")
9 years ago
-- volumedown button
, ((0, 0x1008FF11), spawn "echo - | ~/.xmonad/action-manager/command.sh ~/.xmonad/actioncontrol")
-- Media buttons
, ((0, 0x1008ff14), spawn "clementine --play-pause")
, ((0, 0x1008ff15), spawn "clementine --stop")
, ((0, 0x1008ff16), spawn "clementine --restart-or-previous")
, ((0, 0x1008ff17), spawn "clementine --next")
9 years ago
]
`additionalKeys`
--
-- mod-ctrl-[1..9], Switch to workspace N
--
-- mod-ctrl-[1..9], Switch to workspace N
-- mod-ctrl-shift-[1..9], Move client to workspace N
--
[((m .|. modMask baseConfig , k), windows $ f i)
| (i, k) <- zip (workspaces baseConfig) [xK_F1 .. xK_F9]
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]