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

141 lines
6.5 KiB

9 years ago
import XMonad
import XMonad.Actions.CycleWS
import XMonad.Actions.Minimize(minimizeWindow, withLastMinimized, maximizeWindowAndFocus)
9 years ago
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.SetWMName
9 years ago
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
, startupHook = startupHook desktopConfig >> setWMName "LG3D"
9 years ago
, terminal = "mate-terminal.wrapper"
, workspaces = ["1:web", "2:com"] ++ map show [3..7] ++ ["8:media", "9:div"]
, layoutHook = smartBorders $ fullscreenFull $ avoidStruts $ boringWindows $ minimize $ maximizeWithPadding 0 $ onWorkspace "8:media" Full $ onWorkspaces ["2:com", "9:div"] simpleTabbed $ (Tall 1 0.03 0.5 ||| Full ||| simpleTabbed )
, handleEventHook = handleEventHook desktopConfig <+> fullscreenEventHook
9 years ago
}
8 years ago
`removeKeys`
[(m .|. modMask baseConfig , k)
| (k) <- [xK_1 .. xK_9]
, (m) <- [(0), (shiftMask)]]
9 years ago
-- `removeKeys`
-- [(modMask baseConfig .|. shiftMask, xK_q)]
8 years ago
9 years ago
baseXPConfig = defaultXPConfig {
position = Top
}
workspaceManageHook :: ManageHook
workspaceManageHook = composeAll [
className =? "Firefox" --> doShift "1:web"
,className =? "Thunderbird" --> doShift "2:com"
9 years ago
,className =? "Gajim" --> doShift "2:com"
,className =? "slack" --> doShift "2:com"
9 years ago
,className =? "KeePass2" --> doShift "9:div"
,className =? "rhythmbox" --> doShift "8:media"
,className =? "vlc" --> doShift "8:media"
,className =? "Xmessage" --> doFloat
,className =? "Screenlayout" --> doFloat
9 years ago
]
xmobarActionWrapper :: String -- action
-> String -- output string
-> String
xmobarActionWrapper action = wrap t "</action>"
where t = concat ["<action=`", action, "`>"]
xmobarSwitchWs :: String -> String
xmobarSwitchWs wsName = xmobarActionWrapper action wsName
where action = concat ["xdotool key ISO_Level3_Shift+F", workspace]
workspace = takeWhile (/=':') wsName -- Takes all chars until ':'
9 years ago
main = do
xmobar_proc <- spawnPipe "xmobar"
xmonad $ baseConfig
{ manageHook = (scratchpadManageHook $ W.RationalRect 0.0 0.0 1.0 0.5) <+> workspaceManageHook <+> fullscreenManageHook <+> manageDocks
, logHook = dynamicLogWithPP xmobarPP
{ ppOutput = hPutStrLn xmobar_proc
, ppHidden = xmobarSwitchWs
, ppVisible = wrap "(" ")" .xmobarSwitchWs
, ppTitle = xmobarColor "green" "" . shorten 90
, ppSort = fmap(.scratchpadFilterOutWorkspace) (ppSort xmobarPP)
, ppOrder = \(ws:_:t:_) -> [ ws, t]
}
9 years ago
}
`additionalKeys`
[ ((modMask baseConfig .|. controlMask, xK_l), spawn "xscreensaver-command -lock")
, ((mod1Mask .|. controlMask, xK_l), spawn "xscreensaver-command -lock")
9 years ago
, ((modMask baseConfig .|. controlMask, xK_s), spawn "systemctl hibernate")
-- , ((modMask baseConfig, xK_r), spawn "~/.xmonad/action-manager/command.sh redshift ~/.xmonad/actioncontrol")
-- , ((modMask baseConfig, xK_e), spawn "caja")
9 years ago
, ((0, xK_Print), spawn "scrot")
, ((mod1Mask, xK_Print), spawn "scrot -s")
9 years ago
-- 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), withLastMinimized maximizeWindowAndFocus)
9 years ago
-- 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")
8 years ago
-- Azerty support
, ((modMask baseConfig, xK_semicolon), sendMessage (IncMasterN (-1)))
-- mute button
, ((0, 0x1008FF12), spawn "~/.xmonad/action-manager/command.sh mt ~/.xmonad/actioncontrol")
-- volumeup button
, ((0, 0x1008FF13), spawn "~/.xmonad/action-manager/command.sh + ~/.xmonad/actioncontrol")
-- volumedown button
, ((0, 0x1008FF11), spawn "~/.xmonad/action-manager/command.sh - ~/.xmonad/actioncontrol")
-- Media buttons
, ((0, 0x1008ff14), spawn "rhythmbox-client --play-pause")
, ((0, 0x1008ff15), spawn "rhythmbox-client --stop")
, ((0, 0x1008ff16), spawn "rhythmbox-client --previous")
, ((0, 0x1008ff17), spawn "rhythmbox-client --next")
-- Brightness buttons
, ((0, 0x1008ff02), spawn "~/.xmonad/brightness-adjust +")
, ((0, 0x1008ff03), spawn "~/.xmonad/brightness-adjust -")
-- Displays button (Win+P)
, ((mod4Mask, xK_p), spawn "~/.xmonad/action-manager/command.sh screenlayout ~/.xmonad/actioncontrol")
, ((mod4Mask .|. shiftMask, xK_p), spawn "~/.xmonad/action-manager/command.sh screenlayout-reset ~/.xmonad/actioncontrol")
9 years ago
]
8 years ago
`additionalKeys`
--
-- mod-ctrl-[F1..F9], Switch to workspace N
-- mod-ctrl-shift-[F1..F9], Move client to workspace N
8 years ago
--
[((m .|. modMask baseConfig , k), windows $ f i)
| (i, k) <- zip (workspaces baseConfig) [xK_F1 .. xK_F9]
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]