Advertisement
Not a member of Pastebin yet?
Sign Up,
it unlocks many cool features!
- import System.Posix.Env (getEnv)
- import Data.Maybe (maybe)
- import XMonad
- import XMonad.Util.SpawnOnce
- import XMonad.Util.Run
- import XMonad.Util.XUtils
- import XMonad.Hooks.DynamicLog
- -- import XMonad.Core
- --import XMonad.Config.Prime
- import XMonad.Util.Font
- --import FileLogger
- import Control.Monad
- import Data.List
- import Data.Char (toUpper, toLower)
- import XMonad.Util.EZConfig
- import XMonad.Util.Dmenu
- -- import XMonad.Operations.unGrab
- import XMonad.Layout.Tabbed
- import XMonad.Layout.Grid
- import XMonad.Actions.NoBorders
- import XMonad.Layout.Accordion
- import XMonad.Actions.SpawnOn
- import XMonad.Actions.FloatSnap
- import XMonad.Hooks.SetWMName
- import XMonad.Hooks.ManageDocks
- import XMonad.Util.NamedScratchpad
- import XMonad.Hooks.StatusBar
- import XMonad.Hooks.StatusBar.PP
- import XMonad.Util.WorkspaceCompare (getSortByXineramaRule)
- import Foreign.C.String
- import Control.Monad.State.Class
- import Data.Maybe (isJust)
- import Text.Regex.PCRE ((=~))
- import Control.Applicative ((<$>))
- import Data.List (elemIndex, find)
- import XMonad.Util.NamedWindows (getName)
- import qualified Data.Map as M
- import qualified XMonad.StackSet as W
- -- import XMonad.Config.Desktop
- -- import XMonad.Config.Gnome
- -- import XMonad.Config.Kde
- -- import XMonad.Config.Xfce
- mySB = statusBarProp "xmobar ~/.config/xmobar/xmobarrc" (pure myPP)
- main :: IO ()
- main = xmonad
- . withEasySB mySB defToggleStrutsKey
- $ def
- { modMask = mod4Mask
- ,terminal = myTerminal
- ,normalBorderColor = "#444444"
- ,focusedBorderColor = "#ffffff"
- ,manageHook = newManageHook
- ,startupHook = myStartupHook
- ,layoutHook = avoidStruts $ myLayout
- ,workspaces = myWorkspaces
- ,logHook = dynamicLog
- }
- `additionalKeysP`
- [ ("M-S-l", spawn "xscreensaver-command -lock")
- --,("M-C-s", unGrab *> spawn "scrot -s")
- ,("M-w", spawn myBrowserCommand)
- ,("M-y", spawn "/home/summer/.nix-profile/bin/xmobar /home/summer/.config/xmobar/xmobarrc 2>&1 >/home/summer/.xmonad/xmobar.errors")
- ,("M-<Return>", spawn myTerminal)
- ,("M-x", kill)
- ,("M-<Print>", spawn "bash -c 'cd ~/Pictures/Screenshots && shotgun'")
- ,("M-d", spawn "dmenu_run")
- ,("M-f", withFocused toggleFloat)
- ,("M-'", namedScratchpadAction scratchpads "browser")
- ,("M-g", namedScratchpadAction scratchpads "graphics")
- ,("<XF86MonBrightnessUp>", spawn "lux -a 10%")
- ,("<XF86MonBrightnessDown>", spawn "lux -s 10%")
- -- ,("M-<Minus>", namedScratchpadAction scratchpads "terminals")
- ,("M-=", toggleFull)
- ,("M-<Left>", withFocused $ snapMove L Nothing)
- ,("M-<Right>", withFocused $ snapMove R Nothing)
- ,("M-<Down>", withFocused $ snapMove D Nothing)
- ,("M-<Up>", withFocused $ snapMove U Nothing)
- ]
- where toggleFloat w = windows (\s -> if M.member w (W.floating s)
- then W.sink w s
- else (W.float w (W.RationalRect (1/3) (1/4) (1/2) (4/5)) s))
- myPP = def
- { ppLayout = const "" -- Don't show the layout name
- ,ppSort = getSortByXineramaRule -- Sort left/right screens on the left, non-empty workspaces after those
- ,ppTitle = const "" -- Don't show the focused window's title
- ,ppTitleSanitize = const "" -- Also about window's title
- ,ppVisible = wrap "(" ")" -- Non-focused (but still visible) screen
- }
- -- myScratchPads :: [NamedScratchpad]
- -- myScratchPads = [ NS "browser" spawnBrowser findBrowser manageBrowser ]
- -- where spawnBrowser = myBrowser
- -- findBrowser = className =? "google-chrome-stable"
- -- manageBrowser = customFloating $ W.RationalRect l t w h
- -- where h = 0.9
- -- w = 0.9
- -- t = 0.95 -h
- -- l = 0.95 -w
- -- toggleFull = withFocused (\windowId -> do
- -- { floats <- gets (W.floating . windowset);
- -- if windowId `M.member` floats
- -- then withFocused $ windows . W.sink
- -- else withFocused $ windows . (flip W.float $ W.RationalRect 0 0 1 1) })
- --
- --
- myWorkspaces = [ "1","2","3","4","5","6","7","8","9" ];
- toggleFull = withFocused (\windowId -> do
- {
- floats <- gets (W.floating . windowset);
- if windowId `M.member` floats
- then do
- withFocused $ toggleBorder
- withFocused $ windows . W.sink
- else do
- withFocused $ toggleBorder
- withFocused $ windows . (flip W.float $ W.RationalRect 0 0 1 1)
- } )
- scratchpads = [
- NS "browser" myBrowserCommand (className =? capitalize myBrowser)
- (customFloating $ W.RationalRect 0 0.5 0.5 1)
- --(customFloating $ W.RationalRect (1/4) (1/4) (2/4) (2/4))
- ,NS "graphics" "gimp" (className =? "Gimp")
- (customFloating $ W.RationalRect 0 0 0.5 1)
- -- (customFloating $ W.RationalRect (1/4) (1/4) (2/4) (2/4))
- -- ,NS "terminals" myTerminal (className =? capitalize myTerminal)
- -- (customFloating $ W.RationalRect (1/4) (1/4) (2/4) (2/4))
- ]
- -- runOrRaiseMasterShift :: String -> Query Bool -> X ()
- -- runOrRaiseMasterShift run query = runOrRaiseAndDo run query (\wId -> whenX (elem wId <$> visibleWindows) swapNextScreen
- capitalize :: String -> String
- capitalize "" = ""
- capitalize (x:xs) = toUpper x : map toLower xs
- myBrowser = "google-chrome"
- myBrowserCommand = "google-chrome-stable"
- myTerminal = "alacritty"
- -- workspacesGrouped :: X [(WorkspaceId, [String])]
- -- workspacesGrouped = do
- -- ws <- gets windowset
- -- let x = map (W.workspace) (W.current ws : W.visible ws)
- -- let y = (W.hidden ws)
- -- sequence $ fmap (\v -> fmap ((,) $ W.tag v) (getWorkspaceWindowTitles v)) $ x ++ y
- -- getWorkspaceWindowTitles :: W.Workspace i l Window -> X [String]
- -- getWorkspaceWindowTitles w = do
- -- withDisplay $ \d ->
- -- (liftIO $ forM
- -- (W.integrate' $ W.stack w)
- -- (\z -> getWindowTitle z d)
- -- )
- -- getWindowTitle :: Window -> Display -> IO String
- -- getWindowTitle w d = getTextProperty d w wM_NAME >>= (peekCString . tp_value)
- windowIndex :: Window -> W.StackSet i l Window s sd -> Maybe Int
- windowIndex w s = elemIndex w $ allWindowsInCurrentWorkspace s
- allWindowsInCurrentWorkspace :: W.StackSet i l a sid sd -> [a]
- allWindowsInCurrentWorkspace ws =
- W.integrate' . W.stack . W.workspace . W.current $ ws
- findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
- findM _ [] = return Nothing
- findM f (h:t) = do
- r <- f h
- if r
- then return (Just h)
- else findM f t
- -- findWindowOnCurrentWorkspace :: Query Bool -> (Window -> X()) -> X() -> X()
- -- findWindowOnCurrentWorkspace condition actionIfFound actionIfNotFound = do
- -- windows <- gets (W.index . windowset)
- -- found <- findM (runQuery condition) windows
- -- case found of
- -- Nothing -> actionIfNotFound
- -- Just w -> actionIfFound w
- -- findWindow :: String -> X (Maybe Window)
- -- findWindow regex = do
- -- wmap <- concat <$> (mapM mappings =<< (W.workspaces <$> gets windowset))
- -- :: X [(String, Window)]
- -- return (snd <$> find ((=~ regex) . fst) wmap)
- -- where mappings :: WindowSpace -> X [(String, Window)]
- -- mappings ws = mapM mapping $ W.integrate' (W.stack ws)
- -- mapping w = flip (,) w <$> show <$> getName w
- --
- findWindow :: (Window -> Bool) -> (Window -> X()) -> X() -> X()
- findWindow condition actionIfFound actionIfNotFound = do
- windows <- gets (W.index . windowset)
- let found = find condition windows -- found has type Maybe Window
- case found of
- Nothing -> actionIfNotFound
- Just w -> actionIfFound w
- currentWorkspaceHasWindow :: WindowSet -> Bool
- currentWorkspaceHasWindow = isJust . W.peek
- myStartupHook :: X ()
- myStartupHook = composeAll $
- [ setWMName "Songbird" -- Make this conditional!!! So annoying
- ,spawn "/usr/bin/env xmobar ~/.config/xmobar/xmobarrc"
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- ,spawnOn "1" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- --,spawnOn "2" myTerminal
- ]
- -- else []
- -- where checkWS = do stackset <- gets windowset
- -- currentWorkspaceHasWindow stackset
- myLayout = Grid
- myManageHook :: ManageHook
- myManageHook = composeAll
- [ className =? (capitalize myBrowser) --> doFloat
- ] <+> namedScratchpadManageHook scratchpads
- newManageHook = myManageHook <> manageHook def
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement