Advertisement
nnoell

xmonad.hs v2

Sep 24th, 2011
102
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
Haskell 20.04 KB | None | 0 0
  1. -- Misc
  2. {-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, TypeSynonymInstances, MultiParamTypeClasses #-}
  3.  
  4. -- Imported libraries
  5. import XMonad
  6. import XMonad.Core
  7. import XMonad.Layout
  8. import XMonad.Layout.IM
  9. import XMonad.Layout.Gaps
  10. import XMonad.Layout.Named
  11. import XMonad.Layout.Tabbed
  12. import XMonad.Layout.OneBig
  13. import XMonad.Layout.Master
  14. import XMonad.Layout.Reflect
  15. import XMonad.Layout.MosaicAlt
  16. import XMonad.Layout.NoBorders (noBorders,smartBorders,withBorder)
  17. import XMonad.Layout.ResizableTile
  18. import XMonad.Layout.MultiToggle
  19. import XMonad.Layout.MultiToggle.Instances
  20. import XMonad.Layout.PerWorkspace (onWorkspace)
  21. import XMonad.Layout.Minimize
  22. import XMonad.StackSet (RationalRect (..), currentTag)
  23. import XMonad.Hooks.DynamicLog
  24. import XMonad.Hooks.ManageDocks (avoidStruts,avoidStrutsOn,manageDocks)
  25. import XMonad.Hooks.ManageHelpers
  26. import XMonad.Hooks.UrgencyHook
  27. import XMonad.Hooks.EwmhDesktops
  28. import XMonad.Hooks.SetWMName
  29. import XMonad.Prompt
  30. import XMonad.Prompt.Shell
  31. import XMonad.Prompt.XMonad
  32. import XMonad.Util.Run (spawnPipe)
  33. import XMonad.Util.Scratchpad (scratchpadManageHook, scratchpadSpawnActionCustom)
  34. import XMonad.Util.NamedScratchpad
  35. import XMonad.Actions.CycleWS (nextWS, prevWS, toggleWS, toggleOrView)
  36. import XMonad.Actions.GridSelect
  37. import Data.Monoid
  38. import Data.List (isPrefixOf)
  39. import Graphics.X11.Xlib
  40. import Graphics.X11.ExtraTypes.XF86
  41. import System.Exit
  42. import System.IO (Handle, hPutStrLn)
  43. import qualified XMonad.StackSet as W
  44. import qualified Data.Map as M
  45. import qualified XMonad.Actions.FlexibleResize as Flex
  46.  
  47. -- Main
  48. main :: IO ()
  49. main = do
  50.     workspaceBar            <- spawnPipe myWorkspaceBar
  51.     bottomStatusBar         <- spawnPipe myBottomStatusBar
  52.     topStatusBar            <- spawnPipe myTopStatusBar
  53.     xmonad $ withUrgencyHook NoUrgencyHook defaultConfig
  54.         { terminal           = "urxvtc"
  55.         , modMask            = mod4Mask
  56.         , focusFollowsMouse  = True
  57.         , borderWidth        = 1
  58.         , normalBorderColor  = colorGray
  59.         , focusedBorderColor = colorBlue
  60.         , layoutHook         = myLayoutHook
  61.         , workspaces         = myWorkspaces
  62.         , manageHook         = manageDocks <+> myManageHook
  63.         , logHook            = dynamicLogWithPP $ myDzenPP workspaceBar
  64.         , keys               = myKeys
  65.         , mouseBindings      = myMouseBindings
  66.         , startupHook        = ewmhDesktopsStartup >> setWMName "LG3D"
  67.         }
  68.  
  69. -- Colors
  70. myFont          = "-xos4-terminus-medium-r-normal-*-12-120-72-72-c-60-*-*"
  71. dzenFont        = "-*-montecarlo-medium-r-normal-*-11-*-*-*-*-*-*-*"
  72. colorBlack      = "#000000"
  73. colorBlackAlt   = "#050505"
  74. colorGray       = "#484848"
  75. colorGrayAlt    = "#b8bcb8"
  76. colorDarkGray   = "#161616"
  77. colorWhite      = "#ffffff"
  78. colorWhiteAlt   = "#9d9d9d"
  79. colorDarkWhite  = "#444444"
  80. colorMagenta    = "#8e82a2"
  81. colorMagentaAlt = "#a488d9"
  82. colorBlue       = "#3475aa"
  83. colorBlueAlt    = "#007b8c"
  84. colorRed        = "#d74b73"
  85. colorGreen      = "#99cc66"
  86.  
  87. -- Tab theme
  88. myTabTheme = defaultTheme
  89.     { fontName            = myFont
  90.     , inactiveBorderColor = colorGrayAlt
  91.     , inactiveColor       = colorGray
  92.     , inactiveTextColor   = colorGrayAlt
  93.     , activeBorderColor   = colorGrayAlt
  94.     , activeColor         = colorBlue
  95.     , activeTextColor     = colorDarkGray
  96.     , urgentBorderColor   = colorBlackAlt
  97.     , urgentTextColor     = colorWhite
  98.     , decoHeight          = 14
  99.     }
  100.  
  101. -- Prompt theme
  102. myXPConfig = defaultXPConfig
  103.     { font                = myFont
  104.     , bgColor             = colorBlackAlt
  105.     , fgColor             = colorWhiteAlt
  106.     , bgHLight            = colorBlue
  107.     , fgHLight            = colorDarkGray
  108.     , borderColor         = colorDarkGray
  109.     , promptBorderWidth   = 1
  110.     , height              = 16
  111.     , position            = Top
  112.     , historySize         = 100
  113.     , historyFilter       = deleteConsecutive
  114.     , autoComplete        = Nothing
  115.     }
  116.  
  117. -- GridSelect magenta color scheme
  118. myColorizer = colorRangeFromClassName
  119.     (0x00,0x00,0x00) -- lowest inactive bg
  120.     (0x60,0xA0,0xC0) -- highest inactive bg
  121.     (0x34,0x75,0xAA) -- active bg
  122.     (0xBB,0xBB,0xBB) -- inactive fg
  123.     (0x00,0x00,0x00) -- active fg
  124.     where
  125.         black = minBound
  126.         white = maxBound
  127.  
  128. -- GridSelect theme
  129. myGSConfig colorizer = (buildDefaultGSConfig myColorizer)
  130.     { gs_cellheight  = 50
  131.     , gs_cellwidth   = 200
  132.     , gs_cellpadding = 10
  133.     , gs_font        = myFont
  134.     }
  135.  
  136. -- Scratchpad
  137. manageScratchPad :: ManageHook
  138. manageScratchPad = scratchpadManageHook (W.RationalRect (0) (1/50) (1) (3/4))
  139. scratchPad = scratchpadSpawnActionCustom "urxvtc -name scratchpad"
  140.  
  141. -- Transformers
  142. data TABBED = TABBED deriving (Read, Show, Eq, Typeable)
  143. instance Transformer TABBED Window where
  144.      transform TABBED x k = k (named "TS" (smartBorders (tabbedAlways shrinkText myTabTheme))) (\_ -> x)
  145.  
  146. -- StatusBars
  147. myWorkspaceBar, myBottomStatusBar, myTopStatusBar :: String
  148. myWorkspaceBar    = "dzen2 -x '0' -y '784' -h '16' -w '890' -ta 'l' -fg '" ++ colorWhite ++ "' -bg '" ++ colorBlackAlt ++ "' -fn '" ++ dzenFont ++ "' -p -e ''"
  149. myBottomStatusBar = "/home/nnoell/.scripts/bottomstatusbar.sh"
  150. myTopStatusBar    = "/home/nnoell/.scripts/topstatusbar.sh"
  151.  
  152. -- Layout hook
  153. myLayoutHook = id
  154.     $ gaps [(U,16), (D,16), (L,0), (R,0)]
  155.     $ avoidStruts
  156.     $ minimize
  157.     $ mkToggle (single TABBED)
  158.     $ mkToggle (single REFLECTX)
  159.     $ mkToggle (single REFLECTY)
  160.     $ onWorkspace (myWorkspaces !! 1) webLayouts  --Workspace 1 layouts
  161.     $ onWorkspace (myWorkspaces !! 2) codeLayouts --Workspace 2 layouts
  162.     $ onWorkspace (myWorkspaces !! 3) gimpLayouts --Workspace 3 layouts
  163.     $ onWorkspace (myWorkspaces !! 4) chatLayouts --Workspace 4 layouts
  164.     $ allLayouts
  165.     where
  166.         allLayouts  = myTile ||| myObig ||| myMirr ||| myMosA ||| myTabM
  167.         webLayouts  = myTabs ||| myTabM
  168.         codeLayouts = myTabM ||| myTile
  169.         gimpLayouts = myGimp
  170.         chatLayouts = myChat
  171.         --Layouts
  172.         myTile = named "T"  (smartBorders (ResizableTall 1 0.03 0.5 []))
  173.         myMirr = named "MT" (smartBorders (Mirror myTile))
  174.         myMosA = named "M"  (smartBorders (MosaicAlt M.empty))
  175.         myObig = named "O"  (smartBorders (OneBig 0.75 0.65))
  176.         myTabs = named "TS" (smartBorders (tabbed shrinkText myTabTheme))
  177.         myTabM = named "TM" (smartBorders (mastered 0.01 0.4 $ (tabbed shrinkText myTabTheme)))
  178.         myGimp = named "G"  (withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.20) (Role "gimp-dock") (myMosA))
  179.         myChat = named "C"  (withIM (0.20) (Title "Buddy List") $ Mirror myTile)
  180.  
  181. -- Workspaces
  182. myWorkspaces :: [WorkspaceId]
  183. myWorkspaces = clickable $
  184.     [" TERM " --0
  185.     ," WEBS " --1
  186.     ," CODE " --2
  187.     ," GRFX " --3
  188.     ," CHAT " --4
  189.     ," MUZK " --5
  190.     ," VIDS " --6
  191.     ," OTHR " --7
  192.     ]
  193.     where clickable l = [ "^ca(1,xdotool key super+" ++ show (n) ++ ")" ++ ws ++ "^ca()" |
  194.         (i,ws) <- zip [1..] l,
  195.         let n = if i == 10 then 0 else i ]
  196.  
  197. -- Manage hook
  198. myManageHook :: ManageHook
  199. myManageHook = (composeAll . concat $
  200.     [ [resource     =? r     --> doIgnore                      |   r   <- myIgnores] --ignore desktop
  201.     , [className    =? c     --> doShift (myWorkspaces !! 1)   |   c   <- myWebS   ] --move myWebS windows to workspace 1 by classname
  202.     , [className    =? c     --> doShift (myWorkspaces !! 4)   |   c   <- myChatS  ] --move myChatS windows to workspace 4 by classname
  203.     , [className    =? c     --> doShift (myWorkspaces !! 3)   |   c   <- myGfxS   ] --move myGfxS windows to workspace 4 by classname
  204.     , [className    =? c     --> doShift (myWorkspaces !! 5)   |   c   <- myMusicS ] --move myMusiS windows to workspace 5 by classname
  205.     , [className    =? c     --> doCenterFloat                 |   c   <- myFloatCC] --float center geometry by classname
  206.     , [name         =? n     --> doCenterFloat                 |   n   <- myFloatCN] --float center geometry by name
  207.     , [name         =? n     --> doSideFloat NW                |   n   <- myFloatSN] --float side NW geometry by name
  208.     , [className    =? c     --> doF W.focusDown               |   c   <- myFocusDC] --dont focus on launching by classname
  209.     , [isFullscreen          --> doF W.focusDown <+> doFullFloat]
  210.     ]) <+> manageScratchPad
  211.     where
  212.         role      = stringProperty "WM_WINDOW_ROLE"
  213.         name      = stringProperty "WM_NAME"
  214.         myIgnores = ["desktop","desktop_window"]
  215.         myWebS    = ["Chromium","Firefox"]
  216.         myGfxS    = ["gimp-2.6", "Gimp-2.6", "Gimp", "gimp", "GIMP"]
  217.         myChatS   = ["Pidgin", "Xchat"]
  218.         myMusicS  = ["Clementine"]
  219.         myFloatCC = ["MPlayer", "File-roller", "zsnes", "Gcalctool", "Exo-helper-1", "Gksu"]
  220.         myFloatCN = ["ePSXe - Enhanced PSX emulator", "Seleccione Archivo", "Config Video", "Testing plugin", "Config Sound", "Config Cdrom", "Config Bios", "Config Netplay", "Config Memcards", "About ePSXe", "Config Controller", "Config Gamepads", "Select one or more files to open", "Add media", "Choose a file", "Open Image", "File Operation Progress", "Firefox Preferences", "Preferences", "Search Engines", "Set up sync", "Passwords and Exceptions", "Autofill Options", "Rename File", "Copying files", "Moving files", "File Properties", "Replace", ""]
  221.         myFloatSN = ["Event Tester"]
  222.         myFocusDC = ["Event Tester"]
  223.  
  224. -- myWorkspaceBar config
  225. myDzenPP h = defaultPP
  226.     { ppOutput          = hPutStrLn h
  227.     , ppSep             = " ^fg(#5f656b)| "
  228.     , ppWsSep           = ""
  229.     , ppCurrent         = wrap ("^fg(" ++ colorWhite ++ ")^bg(" ++ colorBlue ++ ")") ("^fg()^bg()")
  230.     , ppUrgent          = wrap ("^fg(" ++ colorWhite ++ ")^bg(" ++ colorGreen ++ ")") ("^fg()^bg()")
  231.     , ppVisible         = wrap ("^fg(" ++ colorWhite ++ ")^bg(" ++ colorGray ++ ")") ("^fg()^bg()")
  232.     , ppHidden          = wrap ("^fg(" ++ colorGrayAlt ++ ")^bg(" ++ colorGray ++ ")") ("^fg()^bg()")
  233.     , ppSort            = fmap (namedScratchpadFilterOutWorkspace.) (ppSort xmobarPP) -- hide "NSP" from workspace list
  234.     , ppHiddenNoWindows = wrap ("^fg(" ++ colorGray ++ ")^bg(" ++ colorBlackAlt ++ ")") ("^fg()^bg()")
  235.     , ppTitle           = wrap ("^fg(" ++ colorWhiteAlt ++ ")^bg(" ++ colorBlackAlt ++ ")") ("^fg()^bg()") . wrap "" " ^fg(9d9d9d)>^fg(#3475aa)>^fg(#5f656b)>"
  236.     , ppLayout          = wrap ("^fg(" ++ colorBlue ++ ")^bg(" ++ colorBlackAlt ++ ")") ("^fg()^bg()") .
  237.         (\x -> case x of
  238.             "Minimize T"                    -> "ReTall"
  239.             "Minimize O"                    -> "OneBig"
  240.             "Minimize TS"                   -> "Tabbed"
  241.             "Minimize TM"                   -> "Master"
  242.             "Minimize M"                    -> "Mosaic"
  243.             "Minimize MT"                   -> "Mirror"
  244.             "Minimize G"                    -> "Mosaic"
  245.             "Minimize C"                    -> "Mirror"
  246.             "Minimize ReflectX T"           -> "^fg(" ++ colorGreen ++ ")ReTall X"
  247.             "Minimize ReflectX O"           -> "^fg(" ++ colorGreen ++ ")OneBig X"
  248.             "Minimize ReflectX TS"          -> "^fg(" ++ colorGreen ++ ")Tabbed X"
  249.             "Minimize ReflectX TM"          -> "^fg(" ++ colorGreen ++ ")Master X"
  250.             "Minimize ReflectX M"           -> "^fg(" ++ colorGreen ++ ")Mosaic X"
  251.             "Minimize ReflectX MT"          -> "^fg(" ++ colorGreen ++ ")Mirror X"
  252.             "Minimize ReflectX G"           -> "^fg(" ++ colorGreen ++ ")Mosaic X"
  253.             "Minimize ReflectX C"           -> "^fg(" ++ colorGreen ++ ")Mirror X"
  254.             "Minimize ReflectY T"           -> "^fg(" ++ colorGreen ++ ")ReTall Y"
  255.             "Minimize ReflectY O"           -> "^fg(" ++ colorGreen ++ ")OneBig Y"
  256.             "Minimize ReflectY MT"          -> "^fg(" ++ colorGreen ++ ")Tabbed Y"
  257.             "Minimize ReflectY TM"          -> "^fg(" ++ colorGreen ++ ")Master Y"
  258.             "Minimize ReflectY M"           -> "^fg(" ++ colorGreen ++ ")Mosaic Y"
  259.             "Minimize ReflectY MT"          -> "^fg(" ++ colorGreen ++ ")Mirror Y"
  260.             "Minimize ReflectY G"           -> "^fg(" ++ colorGreen ++ ")Mosaic Y"
  261.             "Minimize ReflectY C"           -> "^fg(" ++ colorGreen ++ ")Mirror Y"
  262.             "Minimize ReflectX ReflectY T"  -> "^fg(" ++ colorGreen ++ ")ReTall XY"
  263.             "Minimize ReflectX ReflectY O"  -> "^fg(" ++ colorGreen ++ ")OneBig XY"
  264.             "Minimize ReflectX ReflectY TS" -> "^fg(" ++ colorGreen ++ ")Tabbed XY"
  265.             "Minimize ReflectX ReflectY TM" -> "^fg(" ++ colorGreen ++ ")Master XY"
  266.             "Minimize ReflectX ReflectY M"  -> "^fg(" ++ colorGreen ++ ")Mosaic XY"
  267.             "Minimize ReflectX ReflectY MT" -> "^fg(" ++ colorGreen ++ ")Mirror XY"
  268.             "Minimize ReflectX ReflectY G"  -> "^fg(" ++ colorGreen ++ ")Mosaic XY"
  269.             "Minimize ReflectX ReflectY C"  -> "^fg(" ++ colorGreen ++ ")Mirror XY"
  270.         )
  271.     }
  272.  
  273. -- Key bindings
  274. myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
  275. myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
  276.     [ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)                       --Launch a terminal
  277.     , ((mod1Mask, xK_F2), shellPrompt myXPConfig)                                              --Launch Xmonad shell prompt
  278.     , ((modMask .|. shiftMask, xK_F2), xmonadPrompt myXPConfig)                                --Launch Xmonad prompt
  279.     , ((modMask, xK_g), goToSelected $ myGSConfig myColorizer)                                 --Launch GridSelect
  280.     , ((modMask, xK_masculine), scratchPad)                                                    --Scratchpad
  281.     , ((modMask, xK_o), spawn "gksu halt")                                                     --Power off
  282.     , ((modMask .|. shiftMask, xK_o), spawn "gksu reboot")                                     --Reboot
  283.     , ((mod1Mask, xK_F3), spawn "chromium")                                                    --Launch chromium
  284.     , ((modMask, xK_c), kill)                                                                  --Close focused window
  285.     , ((mod1Mask, xK_F4), kill)
  286.     , ((modMask, xK_space), sendMessage NextLayout)                                            --Rotate through the available layout algorithms
  287.     , ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)                 --Reset the layouts on the current workspace to default
  288.     , ((modMask, xK_n), refresh)                                                               --Resize viewed windows to the correct size
  289.     , ((modMask, xK_Tab), windows W.focusDown)                                                 --Move focus to the next window
  290.     , ((modMask, xK_j), windows W.focusDown)
  291.     , ((mod1Mask, xK_Tab), windows W.focusDown)
  292.     , ((modMask, xK_k), windows W.focusUp)                                                     --Move focus to the previous window
  293.     , ((modMask, xK_a), windows W.focusMaster)                                                 --Move focus to the master window
  294.     , ((modMask .|. shiftMask, xK_a), windows W.swapMaster)                                    --Swap the focused window and the master window
  295.     , ((modMask .|. shiftMask, xK_j), windows W.swapDown  )                                    --Swap the focused window with the next window
  296.     , ((modMask .|. shiftMask, xK_k), windows W.swapUp    )                                    --Swap the focused window with the previous window
  297.     , ((modMask, xK_h), sendMessage Shrink)                                                    --Shrink the master area
  298.     , ((modMask .|. shiftMask, xK_Left), sendMessage Shrink)
  299.     , ((modMask, xK_l), sendMessage Expand)                                                    --Expand the master area
  300.     , ((modMask .|. shiftMask, xK_Right), sendMessage Expand)
  301.     , ((modMask .|. shiftMask, xK_h), sendMessage MirrorShrink)                                --MirrorShrink the master area
  302.     , ((modMask .|. shiftMask, xK_Down), sendMessage MirrorShrink)
  303.     , ((modMask .|. shiftMask, xK_l), sendMessage MirrorExpand)                                --MirrorExpand the master area
  304.     , ((modMask .|. shiftMask, xK_Up), sendMessage MirrorExpand)
  305.     , ((modMask, xK_t), withFocused $ windows . W.sink)                                        --Push window back into tiling
  306.     , ((modMask .|. shiftMask, xK_t), rectFloatFocused)                                        --Push window into float
  307.     , ((modMask, xK_f), sendMessage $ XMonad.Layout.MultiToggle.Toggle TABBED)                 --Push layout into tabbed
  308.     , ((modMask .|. shiftMask, xK_x), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTX) --Reflect layout by X
  309.     , ((modMask .|. shiftMask, xK_y), sendMessage $ XMonad.Layout.MultiToggle.Toggle REFLECTY) --Reflect layout by Y
  310.     , ((modMask, xK_m), withFocused minimizeWindow)                                            --Minimize window
  311.     , ((modMask .|. shiftMask, xK_m), sendMessage RestoreNextMinimizedWin)                     --Restore window
  312.     , ((modMask .|. shiftMask, xK_f), fullFloatFocused)                                        --Push window into full screen
  313.     , ((modMask, xK_comma), sendMessage (IncMasterN 1))                                        --Increment the number of windows in the master area
  314.     , ((modMask, xK_period), sendMessage (IncMasterN (-1)))                                    --Deincrement the number of windows in the master area
  315.     , ((modMask , xK_d), spawn "killall dzen2 trayer")                                         --Kill dzen2 and trayer
  316.     , ((modMask , xK_s), spawn "xscreensaver-command -lock")                                   --Lock screen
  317.     , ((modMask .|. shiftMask, xK_q), io (exitWith ExitSuccess))                               --Quit xmonad
  318.     , ((modMask, xK_q), restart "xmonad" True)                                                 --Restart xmonad
  319.     , ((modMask, xK_comma), toggleWS)                                                          --Toggle to the workspace displayed previously
  320.     , ((mod1Mask, xK_masculine), toggleOrView (myWorkspaces !! 0))                             --Move to Workspace 0
  321.     , ((mod1Mask .|. controlMask, xK_Left),  prevWS)                                           --Move to previous Workspace
  322.     , ((modMask, xK_Left), prevWS)
  323.     , ((modMask, xK_Right), nextWS)                                                            --Move to next Workspace
  324.     , ((mod1Mask .|. controlMask, xK_Right), nextWS)
  325.     , ((0, xF86XK_AudioMute), spawn "sh /home/nnoell/.scripts/volosd.sh mute")                 --Mute/unmute volume
  326.     , ((0, xF86XK_AudioRaiseVolume), spawn "sh /home/nnoell/.scripts/volosd.sh up")            --Raise volume
  327.     , ((0, xF86XK_AudioLowerVolume), spawn "sh /home/nnoell/.scripts/volosd.sh down")          --Lower volume
  328.     , ((0, xF86XK_AudioNext), spawn "ncmpcpp next")                                            --next song
  329.     , ((0, xF86XK_AudioPrev), spawn "ncmpcpp prev")                                            --prev song
  330.     , ((0, xF86XK_AudioPlay), spawn "ncmpcpp toggle")                                          --toggle song
  331.     , ((0, xF86XK_AudioStop), spawn "ncmpcpp stop")                                            --stop song
  332.     , ((0, xF86XK_MonBrightnessUp), spawn "sh /home/nnoell/.scripts/briosd.sh")                --Raise brightness
  333.     , ((0, xF86XK_MonBrightnessDown), spawn "sh /home/nnoell/.scripts/briosd.sh")              --Lower brightness
  334.     , ((0, xF86XK_ScreenSaver), spawn "xscreensaver-command -lock")                            --Lock screen
  335.     , ((0, xK_Print), spawn "scrot")                                                           --Take a screenshot
  336.     ]
  337.     ++
  338.     [((m .|. modMask, k), windows $ f i)                                                       --Switch to n workspaces and send client to n workspaces
  339.       | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
  340.       , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
  341.     ++
  342.     [((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))                --Switch to n screens and send client to n screens
  343.       | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
  344.       , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
  345.     where
  346.         fullFloatFocused = withFocused $ \f -> windows =<< appEndo `fmap` runQuery doFullFloat f
  347.         rectFloatFocused = withFocused $ \f -> windows =<< appEndo `fmap` runQuery (doRectFloat $ RationalRect 0.05 0.05 0.9 0.9) f
  348.  
  349. -- Mouse bindings
  350. myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
  351.     [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w >> windows W.shiftMaster)) -- set the window to floating mode and move by dragging
  352.     , ((modMask, button2), (\w -> focus w >> windows W.shiftMaster))                      -- raise the window to the top of the stack
  353.     , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))                   -- set the window to floating mode and resize by dragging
  354.     , ((modMask, button4), (\_ -> prevWS))                                                -- switch to previous workspace
  355.     , ((modMask, button5), (\_ -> nextWS))                                                -- switch to next workspace
  356.     ]
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement