xmonad-config/xmonad.hs

532 lines
20 KiB
Haskell
Raw Normal View History

2017-12-10 01:14:39 +01:00
-- My xmonad configuration, based on the example.hs of the xmonad project
-- including best practises.
-- https://github.com/xmonad/xmonad-contrib/blob/master/XMonad/Config/Example.hs
2017-12-10 22:52:41 +01:00
{-# LANGUAGE FlexibleContexts, OverloadedStrings #-}
2017-12-10 01:14:39 +01:00
module Main (main) where
import Data.Ratio ((%))
import Data.List (sort, isSuffixOf)
import Text.EditDistance
2017-12-08 19:32:06 +01:00
import System.Exit
import XMonad
import XMonad.Actions.CycleWS
2017-12-11 09:56:34 +01:00
import XMonad.Actions.UpdatePointer
2017-12-08 19:32:06 +01:00
import XMonad.Config.Desktop
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageHelpers
2017-12-10 01:14:39 +01:00
import XMonad.Layout.NoBorders (noBorders, smartBorders)
import XMonad.Layout.ResizableTile (ResizableTall(..))
import XMonad.Layout.Spacing
import XMonad.Layout.ToggleLayouts (ToggleLayout(..), toggleLayouts)
2017-12-08 19:32:06 +01:00
import XMonad.Prompt
2017-12-10 01:14:39 +01:00
import XMonad.Prompt.ConfirmPrompt
import XMonad.Prompt.Shell
import XMonad.Util.EZConfig
import qualified Solarized as S
import qualified XMonad.StackSet as W
2017-12-08 19:32:06 +01:00
2017-12-10 01:14:39 +01:00
-- Contructors imports
import XMonad.Core (XConfig)
import XMonad.Hooks.ManageDocks (AvoidStruts)
import XMonad.Layout.LayoutModifier (ModifiedLayout)
wkspcs :: [String]
-------- ["●", "◕", "◑", "◔", "◯", "◐", "◒", "◓", "☦", "λ"]
2017-12-10 22:52:41 +01:00
-------- ["α", "β", "γ", "δ", "ε", "ζ", "η", "θ", "ι", "κ"]
wkspcs = [ wrap "<fn=1>" "</fn>" "\xF0E0" --  email
, wrap "<fn=1>" "</fn>" "\xF086" --  chat
, wrap "<fn=1>" "</fn>" "\xF121" --  work
, wrap "<fn=1>" "</fn>" "\xF126" --  work
, wrap "<fn=1>" "</fn>" "\xF120" --  work
, wrap "<fn=1>" "</fn>" "\xF09C" --  password
, wrap "<fn=1>" "</fn>" "\xF16C" --  web work
, wrap "<fn=1>" "</fn>" "\xF025" --  sound
, wrap "<fn=1>" "</fn>" "\xF269" --  web perso
, wrap "<fn=1>" "</fn>" "\xF03D" --  movie
]
2017-12-10 01:14:39 +01:00
barPP = def
{ ppCurrent = xmobarColor' S.orange
, ppVisible = xmobarColor' S.yellow -- other screen
, ppHidden = xmobarColor' S.foreground -- other workspaces with windows
, ppHiddenNoWindows = xmobarColor' S.foregroundll -- other workspaces
, ppSep = " "
2017-12-10 22:52:41 +01:00
, ppWsSep = " "
2017-12-10 01:14:39 +01:00
, ppLayout = printLayout
, ppTitle = printTitle
2017-12-08 19:32:06 +01:00
}
2017-12-10 01:14:39 +01:00
where xmobarColor' fg = xmobarColor fg S.base03
printLayout s | "Mirror ResizableTall" `isSuffixOf` s = "[ — ]"
printLayout s | "ResizableTall" `isSuffixOf` s = "[ | ]"
printLayout "Full" = "[ F ]"
printLayout l = "[" ++ l ++ "]"
printTitle t = let t' = shorten 120 t
in xmobarColor' S.foregroundll "« "
++ xmobarColor' S.foregroundhl t'
++ xmobarColor' S.foregroundll " »"
bar :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
bar conf = statusBar "xmobar /home/eeva/.xmonad/xmobarrc" barPP hideBarsKey conf
where hideBarsKey XConfig{modMask = modm} = (modm, xK_b)
2017-12-11 09:56:34 +01:00
lh = do
ls <- dynamicLogString def
xmonadPropLog ls
updatePointer (0.5,0.5) (0,0)
2017-12-10 01:14:39 +01:00
myConfig = desktopConfig
{ modMask = mod4Mask -- Use the "Win" key for the mod key
, manageHook = myManageHook <+> manageHook desktopConfig
, layoutHook = desktopLayoutModifiers $ myLayouts
2017-12-11 09:56:34 +01:00
, logHook = lh
2017-12-10 01:14:39 +01:00
, terminal = "/run/current-system/sw/bin/kitty"
, workspaces = wkspcs
, normalBorderColor = S.base03
, focusedBorderColor = S.violet
, borderWidth = 5
}
2017-12-08 19:32:06 +01:00
2017-12-10 01:14:39 +01:00
`additionalKeysP` -- Add some extra key bindings:
[ ("M-S-q", confirmPrompt myXPConfig "exit" (io exitSuccess))
, ("<Tab>-b", sendMessage (Toggle "Full"))
2017-12-10 01:14:39 +01:00
, ("<XF86MonBrightnessDown>", spawn "/run/current-system/sw/bin/xbacklight -10")
, ("<XF86MonBrightnessUp>", spawn "/run/current-system/sw/bin/xbacklight +10")
, ("M-<Delete>", kill)
, ("M-<Down>", windows W.focusDown)
, ("M-<Esc>", sendMessage (Toggle "Full"))
2017-12-11 09:56:34 +01:00
, ("M-$", sendMessage (Toggle "Full"))
2017-12-10 01:14:39 +01:00
, ("M-<Left>", prevWS)
2017-12-11 09:56:34 +01:00
, ("M-e", nextScreen)
2017-12-10 01:14:39 +01:00
, ("M-<Right>", nextWS)
, ("M-<Tab>", toggleWS)
, ("M-<Up>", windows W.focusUp)
, ("M-S-<Delete>", spawn "/run/current-system/sw/bin/i3lock-fancy -g -p")
, ("M-S-<Left>", shiftToPrev >> prevWS)
, ("M-S-<Right>", shiftToNext >> nextWS)
2017-12-10 22:56:01 +01:00
, ("M-S-p", shellPrompt myXPConfig)
2017-12-10 22:52:41 +01:00
, ("M-S-s", spawn "sleep 0.2 ; /run/current-system/sw/bin/scrot -s /tmp/screenSel.png")
, ("M-p", fuzzyPrompt myXPConfig)
, ("M-s", spawn "/run/current-system/sw/bin/scrot /tmp/screen.png")
2017-12-10 01:14:39 +01:00
]
`additionalKeys`-- Add some more (automatic) key bindings:
[ ((mod4Mask .|. mask, key), windows $ actionWith tag)
| (tag, key) <- zip wkspcs [ xK_F1 .. ]
, (mask, actionWith) <- zip [ 0, shiftMask ] [ W.view, W.shift ] ]
myLayouts = smartBorders $ toggleLayouts (noBorders Full) others
2017-12-08 19:32:06 +01:00
where
2017-12-10 01:14:39 +01:00
resizableTall = ResizableTall 1 (2 % 1) (1/2) []
others = smartSpacingWithEdge 5 $ resizableTall ||| (Mirror resizableTall)
myXPConfig = def
{ position = Top
, alwaysHighlight = True
, bgColor = S.magenta
, bgHLight = S.base0
, borderColor = S.magenta
, defaultText = ""
, fgColor = S.base02
, fgHLight = S.base03
, font = "xft:Fira Code:style=Regular:size=9"
, height = 24
, promptBorderWidth = 5
}
2017-12-08 19:32:06 +01:00
2017-12-10 01:14:39 +01:00
-- Use the `xprop' tool to get the info you need for these matches.
-- For className, use the second value that xprop gives you.
myManageHook = composeOne
[ className =? "mpv" -?> doFullFloat <+> (doShift $ last wkspcs)
, className =? "Pavucontrol" -?> doShift $ wkspcs !! 7
, className =? "qutebrowser" -?> doShift $ wkspcs !! 5
, isDialog -?> doCenterFloat
-- Move transient windows to their parent:
, transience
]
-- Finally:
main = xmonad =<< bar myConfig
-- Slightly taken from
-- https://mail.haskell.org/pipermail/xmonad/2010-October/010671.html
data FuzzySpawn = FuzzySpawn deriving (Read, Show)
2017-12-10 22:56:01 +01:00
instance XPrompt FuzzySpawn where showXPrompt _ = "RunC: "
2017-12-10 01:14:39 +01:00
fuzzyPrompt config = do
cmds <- io getCommands
let compl s
| null s = []
| otherwise = let weight c = levenshteinDistance defaultEditCosts s c
in map snd $ take 20 $ sort $ map (\c -> (weight c,c)) cmds
mkXPrompt FuzzySpawn config (return . compl) spawn
--- import qualified Data.Map as Map
--- import XMonad
--- import XMonad.Util.EZConfig
--- import XMonad.Layout.Tabbed
--- import XMonad.Hooks.ManageDocks
--- import XMonad.Hooks.DynamicLog
--- import XMonad.Layout.NoBorders
--- import XMonad.Actions.SwapWorkspaces
--- import XMonad.Prompt
--- import XMonad.Prompt.Shell
---
--- -- Solarized colours.
--- activeBackColor = "#073642"
--- --activeForeColor = "#93A1A1" -- base1
--- activeForeColor = "#EEE8D5" -- base2
--- passiveForeColor = "#2AA198"
---
--- yoTabbed = tabbed shrinkText $ def
--- { fontName = "xft:Hack:size=10"
--- , activeBorderColor = activeForeColor
--- , activeTextColor = activeForeColor
--- , activeColor = activeBackColor
--- , inactiveBorderColor = "#555555"
--- , inactiveTextColor = "#555555"
--- , inactiveColor = "#000000"
--- }
--- simpleTall = Tall 1 (1/100) (1/2)
--- yoLayouts = smartBorders $ (Mirror simpleTall ||| simpleTall ||| yoTabbed)
---
--- yoPromptXP = def
--- { bgColor = activeBackColor
--- , borderColor = activeForeColor
--- , fgColor = activeForeColor
--- , fgHLight = "#073642"
--- , bgHLight = "#859900"
--- , promptKeymap = emacsLikeXPKeymap
--- , font = "xft:Hack:size=12"
--- }
---
--- yoConfig = def
--- { terminal = "termite"
--- , modMask = mod4Mask
--- , focusedBorderColor = activeForeColor
--- , layoutHook = yoLayouts
--- }
--- `additionalKeysP`
--- [ ( "M-<Return>", spawn $ "emacs")
---
--- , ("<XF86AudioMute>", spawn "pamixer -t")
--- , ("M-<F5>" , spawn "pamixer -d 1")
--- , ("M-<F6>" , spawn "pamixer -i 1")
---
--- , ("M-<F7>" , spawn "xbacklight -dec 5")
--- , ("M-<F8>" , spawn "xbacklight -inc 5")
---
--- , ("M-<F9>" , spawn "setxkbmap dvorak")
--- , ("M-<F10>", spawn "setxkbmap fr" )
--- , ("M-<F11>", spawn "setxkbmap ru" )
--- , ("M-<F12>", spawn "setxkbmap ro" )
---
--- , ("M-C-<Right>", swapTo Next)
--- , ("M-C-<Left>" , swapTo Prev)
---
--- , ("M-r", shellPrompt yoPromptXP)
--- ]
--- `removeKeysP`
--- [ "M-q" ]
---
--- yoXmobarPP = def
--- { ppCurrent = xmobarColor' activeForeColor . activePad
--- , ppVisible = xmobarColor' activeForeColor -- other screen
--- , ppHidden = xmobarColor' passiveForeColor -- other workspaces with windows
--- , ppHiddenNoWindows = xmobarColor' activeBackColor -- other workspaces
--- , ppSep = " "
--- , ppLayout = printLayout
--- , ppTitle = printTitle
--- }
--- where xmobarColor' fg = xmobarColor fg "#000000"
---
--- printLayout "Tall" = "[|]"
--- printLayout "Mirror Tall" = "[—]"
--- printLayout "Tabbed Simplest" = "[□]"
--- printLayout l = "[" ++ l ++ "]"
---
--- printTitle t = let t' = shorten 120 t
--- in xmobarColor' passiveForeColor "[ "
--- ++ xmobarColor' passiveForeColor t'
--- ++ xmobarColor' passiveForeColor " ]"
---
--- activePad s = xmobarColor' bracketColor " >"
--- ++ s
--- ++ xmobarColor' bracketColor "< "
--- bracketColor = "#B58900"
---
--- xmobarCmd = "xmobar /home/scolobb/.xmonad/xmobarrc"
---
--- main = do
--- spawn "stalonetray --geometry 5x1+1000 --icon-size 20 -bg '#000000'"
--- spawn "nm-applet"
--- spawn "seafile-applet"
--- spawn "syndaemon"
--- xmonad =<< statusBar xmobarCmd yoXmobarPP hideBarsKey yoConfig
--- where hideBarsKey XConfig{modMask = modm} = (modm, xK_b)
--- import Codec.Binary.UTF8.String
--- import Graphics.X11.ExtraTypes.XF86
--- import LemonBar
--- import qualified Solarized as S
--- import qualified Data.Map as M
--- import qualified XMonad.StackSet as W
--- import System.Exit
--- import System.IO
--- import Text.Printf
--- import XMonad
--- import XMonad.Actions.CycleWS
--- import XMonad.Config.Desktop
--- import XMonad.Hooks.DynamicLog
--- import XMonad.Hooks.EwmhDesktops
--- import XMonad.Hooks.ManageDocks
--- import XMonad.Hooks.ManageHelpers
--- import XMonad.Layout.IndependentScreens
--- import XMonad.Layout.LayoutCombinators hiding ( (|||) )
--- import XMonad.Layout.Reflect
--- import XMonad.Prompt
--- import XMonad.Prompt.Shell(shellPrompt)
--- import XMonad.Util.Font
--- import XMonad.Util.Loggers
--- -- import XMonad.Util.Run
---
--- main = do
--- spawn bar
--- xmonad $ docks $ ewmh desktopConfig
--- { manageHook = myManageHook <+> manageDocks <+> manageHook defaultConfig
--- , layoutHook = myLayout
--- , logHook = maLogouk
--- , modMask = mod4Mask -- Rebind to Logo key
--- , workspaces = ["●", "◕", "◑", "◔", "◯", "◐", "◒", "◓", "☦"]
--- , borderWidth = 0
--- , keys = myKeys
--- , terminal = "/run/current-system/sw/bin/kitty"
--- , handleEventHook = handleEventHook defaultConfig <+> fullscreenEventHook
--- }
---
--- sym "Tall" = "|"
--- sym "Mirror Tall" = "-"
--- sym "Full" = "F"
--- sym _ = "◓"
---
--- maLogouk = dynamicLogWithPP $ defaultPP
--- { ppOutput = printToFile
--- , ppCurrent = LemonBar.color S.orange S.base03 . LemonBar.underline -- . sym
--- , ppVisible = LemonBar.color S.yellow S.base03 . LemonBar.underline -- . sym
--- , ppHidden = LemonBar.color S.base2 S.base03 . LemonBar.underline -- . sym
--- , ppHiddenNoWindows = LemonBar.color S.base01 S.base03 -- . sym
--- , ppLayout = sym
--- , ppTitle = LemonBar.fColor S.violet . shorten 70
--- , ppSep = " "
--- }
---
--- printToFile :: String -> IO ()
--- printToFile s = do
--- h <- openFile "/tmp/monitors/xmonad" WriteMode
--- hPutStrLn h $ decodeString s
--- -- xxxxxxxxxxxx
--- -- v----------------|
--- -- Hacky hack to fix the broken fix of dynamicLogWithPP
--- hClose h
---
--- myManageHook = composeAll
--- [ className =? "float" --> doCenterFloat
--- , manageDocks ]
---
--- ------------------------------------------------------------------------
--- -- LogHook. Dynamically outputs logs nicely formatted for dzen2
--- --
--- -- myLogHook h = dynamicLogWithPP $ defaultPP {
--- -- ppCurrent = dzenColor "#cb4b16" "#eee8d5",
--- -- ppVisible = dzenColor "#657b83" "#eee8d5",
--- -- ppHiddenNoWindows = dzenColor "#93a1a1" "#eee8d5",
--- -- ppLayout = dzenColor "#6c71c4" "#eee8d5",
--- -- ppTitle = (dzenColor "#cb4b16" "") . (fixedWidth 256),
--- -- ppSep = " ",
--- -- ppWsSep = " ",
--- -- ppOutput = hPutStrLn h
--- -- }
--- -- where
--- -- fixedWidth n l = take (n+5) $ l ++ (cycle ".")
---
---
--- ------------------------------------------------------------------------
--- -- StatusBar. Call lemonbar
--- bar = printf
--- "pkill lemonbar; /home/eeva/bin/mkstatus.sh | \
--- \ lemonbar -g 1919x24+0+0 \
--- \ -f '%s' \
--- \ -f '%s' \
--- \ -u %d -B '%s' -F '%s' -U '%s'"
--- --"tewi:style=Regular:antialias=false:autohint=false"
--- "Iosevka:size=10"
--- "DejaVu Sans Mono:size=10"
--- (2 :: Int)
--- S.base03
--- S.base0
--- S.violet
---
--- myLayout = (avoidStruts $ tiled ||| Mirror tiled) ||| Full
--- where
--- tiled = Tall 1 (3/100) (1/2)
---
--- -- Prompt config
--- myXPConfig = defaultXPConfig {
--- position = Top,
--- promptBorderWidth = 5,
--- font = "xft:tewi:style=Regular:antialias=false:autohint=false",
--- height = 24,
--- borderColor = S.base03,
--- bgHLight = S.base02,
--- fgHLight = S.magenta,
--- bgColor = S.base03,
--- fgColor = S.base0,
--- defaultText = ""
--- }
---
--- ------------------------------------------------------------------------
--- -- Key bindings. Add, modify or remove key bindings here.
--- --
--- myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
--- [
--- -- launch dmenu
--- --((modm, xK_p), spawn "dmenu_run -b -l 3")
--- -- launch prompt
--- ((modm, xK_p), shellPrompt myXPConfig)
---
--- -- close focused window
--- , ((modm, xK_Delete), kill)
---
--- -- Rotate through the available layout algorithms
--- , ((modm, xK_space ), sendMessage NextLayout)
--- --, ((modm .|. shiftMask xK_Tab ), sendMessage PreviousLayout)
---
--- -- Reset the layouts on the current workspace to default
--- , ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
---
--- -- Resize viewed windows to the correct size
--- , ((modm, xK_n ), refresh)
---
--- -- Move focus to the master window
--- , ((modm, xK_m ), windows W.focusMaster )
---
--- -- Swap the focused window and the master window
--- , ((modm, xK_BackSpace), windows W.swapMaster)
---
--- -- Move focus to the next window
--- , ((modm, xK_j ), windows W.focusDown)
--- , ((modm, xK_Down ), windows W.focusDown)
---
--- -- Move focus to the previous window
--- , ((modm, xK_k ), windows W.focusUp )
--- , ((modm, xK_Up ), windows W.focusUp)
---
--- -- Swap the focused window with the next window
--- , ((modm .|. shiftMask, xK_j ), windows W.swapDown )
--- , ((modm .|. shiftMask, xK_Down ), windows W.swapDown )
---
--- -- Swap the focused window with the previous window
--- , ((modm .|. shiftMask, xK_k ), windows W.swapUp )
--- , ((modm .|. shiftMask, xK_Up ), windows W.swapUp )
---
--- -- Shrink the master area
--- , ((modm, xK_h ), sendMessage Shrink)
---
--- -- Expand the master area
--- , ((modm, xK_l ), sendMessage Expand)
---
--- -- Move to next Workspace
--- , ((modm, xK_Right ), nextWS)
---
--- -- Move to previous Workspace
--- , ((modm, xK_Left ), prevWS)
---
--- -- Move focused window to next Workspace
--- , ((modm .|. shiftMask, xK_Right ), shiftToNext >> nextWS)
---
--- -- Move focused window to previous Workspace
--- , ((modm .|. shiftMask, xK_Left ), shiftToPrev >> prevWS)
---
--- -- Cycle between windows
--- , ((modm , xK_Tab ), toggleWS)
---
--- -- Push window back into tiling
--- , ((modm, xK_t ), withFocused $ windows . W.sink)
---
--- -- Increment the number of windows in the master area
--- , ((modm , xK_comma ), sendMessage (IncMasterN 1))
---
--- -- Deincrement the number of windows in the master area
--- , ((modm , xK_period), sendMessage (IncMasterN (-1)))
---
--- -- close focused window
--- , ((modm .|. shiftMask, xK_c ), kill)
---
--- -- Swap the focused window and the master window
--- , ((modm, xK_Return), windows W.swapMaster)
---
--- -- run my terminal
--- , ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
---
--- -- lock my session
--- --, ((modm .|. shiftMask, xK_Delete), spawn "/usr/bin/sxlock -f \"-*-ubuntu mono-*-r-*-*-*-*-*-*-*-*-*-*\"")
--- , ((modm .|. shiftMask, xK_Delete), spawn "/run/current-system/sw/bin/i3lock-fancy -g -p")
---
--- -- quit xmonad
--- , ((modm .|. shiftMask, xK_q), io (exitWith ExitSuccess))
---
--- -- Raise volume (XF86XK_AudioRaiseVolume)
--- , ((0 , xF86XK_AudioRaiseVolume), spawn "/home/eeva/prefix/bin/volume up")
---
--- -- Lower volume (XF86XK_AudioLowerVolume)
--- , ((0 , xF86XK_AudioLowerVolume), spawn "/home/eeva/prefix/bin/volume down")
---
--- -- Mute volume (xF86XK_AudioMute)
--- , ((0 , xF86XK_AudioMute), spawn "/home/eeva/prefix/bin/volume toggle")
---
--- -- Playlist play (xK_F7)
--- , ((0 , xK_F7), spawn "/usr/bin/notify-send \"Current song\" \"$(mpc -h ~/.config/mpd/mpd.socket | head -n 1)\"")
---
--- -- Playlist play (xK_F8)
--- , ((0 , xK_F8), spawn "/home/eeva/prefix/bin/playlist toggle")
---
--- -- Playlist stop (xK_F9)
--- , ((0 , xK_F9), spawn "/home/eeva/prefix/bin/playlist stop")
---
--- -- Launch App (XF86XK_Launch1)
--- , ((0 , xF86XK_Launch1), spawn "/usr/bin/firefox")
---
--- -- Adjust Brightness up (xF86XK_MonBrightnessUp)
--- , ((0 , xF86XK_MonBrightnessUp), spawn "/run/current-system/sw/bin/xbacklight +10")
---
--- -- Adjust Brightness down (xF86XK_MonBrightnessDown)
--- , ((0 , xF86XK_MonBrightnessDown), spawn "/run/current-system/sw/bin/xbacklight -10")
--- ]
--- ++
---
--- --
--- -- mod-[1..9], Switch to workspace N
--- --
--- -- mod-[1..9], Switch to workspace N
--- -- mod-shift-[1..9], Move client to workspace N
--- --
--- [((m .|. modm, k), windows $ f i)
--- | (i, k) <- zip (XMonad.workspaces conf) [xK_F1 .. xK_F9]
--- , (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 .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f))
--- | (key, sc) <- zip [xK_z, xK_e, xK_r] [0..]
--- , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]