{-# OPTIONS_GHC -fno-warn-missing-signatures #-} -- | Configuration with defaults I like. module Main (main) where import qualified Data.Map as M import Data.Maybe import Data.Monoid import Data.Ratio ((%)) import System.IO (Handle) import XMonad hiding (workspaces) import XMonad.Actions.GridSelect import XMonad.Hooks.DynamicLog import XMonad.Hooks.ManageDocks import XMonad.Layout.Hidden import XMonad.Layout.Mosaic import XMonad.Layout.Reflect import XMonad.Layout.Spiral import XMonad.StackSet hiding (float) import XMonad.Util.Keyboard import XMonad.Util.MediaKeys import XMonad.Util.NamedWindows import XMonad.Util.Run import XMonad.Util.Volume -- TODO wallpaper? -- | IO action of the whole thing main :: IO () main = xmonad . config' =<< spawnPipe "xmobar" where config' = myConfig -- | Custom configuration taking in one pipe to xmobar myConfig xmproc = docks $ def { terminal = "alacritty" , keys = newKeys , layoutHook = myLayout , logHook = vLogHook xmproc , manageHook = myManageHook <+> manageDocks , handleEventHook = docksEventHook , startupHook = docksStartupHook } -- | get the current music playing (assumed to be in number 5) musicString :: X String musicString = do winset <- gets windowset wt <- maybe (pure "") (fmap show . getName) . fmap snd . listToMaybe $ zip ((fmap tag . workspaces) winset) (allWindows winset) pure . xmobarColor "green" "black" . take 40 $ wt -- | Provides custom hooks to xmonad. This disables printing the window title/connects xmobar and xmonad. vLogHook :: Handle -> X () vLogHook xmproc = musicString >>= \m -> dynamicLogWithPP xmobarPP { ppOutput = hPutStrLn xmproc , ppTitle = const m , ppLayout = const "" , ppHiddenNoWindows = id , ppHidden = xmobarColor "darkorange" "black" , ppVisible = xmobarColor "yellow" "black" } -- | Doesn't work on spotify myManageHook :: Query (Endo WindowSet) myManageHook = composeAll (shifts : floats) where shifts = className =? "Firefox" --> doF (shift "5") floats = fmap (--> doFloat) (classes <> resources) resources = fmap (resource =?) resourceNames classes = fmap (className =?) classNames resourceNames = [ "launcher", "qemu-system-arm" ] classNames = [ "Gimp-2.8", "libreoffice-write", "Gimp", "keepassx", "xviewer", "qemu-system-x86_64" ] mkSmall :: Window -> X () mkSmall = flip tileWindow (Rectangle 850 150 600 400) -- | Custom keymaps to adjust volume, brightness, and myKeys :: XConfig t -> M.Map (KeyMask, KeySym) (X ()) myKeys XConfig { XMonad.modMask = modm } = mediaKeys . M.fromList $ [ --volume control ((modm, xK_Up), raiseVolume (5 :: Word)) , ((modm, xK_Down), lowerVolume (5 :: Word)) , ((modm, xK_BackSpace), toggleMute) --personal (extra) media keys , ((modm, xK_Page_Down), audioNext) , ((modm, xK_Page_Up), audioPrev) , ((modm, xK_Home), audioPlayPause) , ((modm, xK_Return), audioPlayPause) --program shortcuts , ((modm, xK_q), spawn "spotify") , ((modm .|. shiftMask, xK_t), spawn "thunderbird") , ((modm .|. shiftMask, xK_n), spawn "firefox") , ((modm .|. controlMask, xK_Return), spawn "gnome-terminal") --launch bar , ((modm, xK_p), spawn "$(yeganesh -x)") --screenshots , ((0, xK_Print), spawn "cd ~/.screenshots && scrot") -- open scratchpad , ((modm .|. shiftMask, xK_p), withFocused (mconcat . sequence [float, mkSmall])) -- TODO: keybindings to move all windows in a workspace to another -- workspace? --shutdown etc. , ((modm .|. shiftMask, xK_End), spawn "shutdown now") -- lock screen , ((controlMask, xK_End), spawn "slock") --switch keyboards , ((modm, xK_F1), setLang def) , ((modm, xK_F2), setLang tibetan) , ((modm, xK_F3), setLang accented) , ((modm, xK_F4), setLang français) , ((modm, xK_F5), setLang deutsch) , ((modm, xK_F6), setLang dansk) , ((modm, xK_F7), setLang dzongkha) -- hide windows , ((modm .|. shiftMask, xK_h), withFocused (mconcat . sequence [hide, hideWindow])) , ((modm, xK_u), popNewestHiddenWindow >> withFocused reveal) -- grid select , ((modm, xK_g), goToSelected def) -- Mosaic adjustment , ((modm, xK_a), sendMessage Taller) , ((modm, xK_s), sendMessage Wider) , ((modm, xK_r), sendMessage Reset) ] -- | Function giving keybindings to undo keysToRemove :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) keysToRemove XConfig { XMonad.modMask = modm } = M.fromList [ ((modm, xK_p), pure ()) ] -- | Gives a better ratio for the master pane and lets us spiral windows myLayout = (avoidStruts . hiddenWindows $ mosaic 1.33 mosaicSettings ||| normalPanes ||| reflectHoriz normalPanes ||| Full) ||| hiddenWindows (spiral (6/7)) where normalPanes = Tall 1 (3/100) (3/7) mosaicSettings = take 6 $ iterate (* (4 % 5)) 1 -- | Make new key layout from a given keyboard layout newKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) newKeys x = myKeys x `M.union` (keys def x `M.difference` keysToRemove x)