Xmonad/Config archive/thoughtpolice's xmonad.hs

From HaskellWiki
Jump to navigation Jump to search


--
-- The horrible thing about the Two Minutes Hate was not that 
-- one was obliged to act a part, but that it was impossible 
-- to avoid joining in.
--
import XMonad
import System.Exit
import qualified XMonad.StackSet as W
import qualified Data.Map        as M
import qualified XMonad.Actions.Submap as SM
import qualified XMonad.Actions.Search as S
import XMonad.Hooks.ManageDocks
import XMonad.Prompt
import XMonad.Prompt.Shell
import XMonad.Prompt.Ssh
import XMonad.Util.EZConfig 

main :: IO ()
main = xmonad $ defaultConfig {
           terminal   = "urxvt +sb -fg white -bg black"
         , workspaces = ["web/irc","code"] ++ map show [3..9]
         , keys       = myKeys
         , manageHook = composeAll [className =? "Firefox" --> doF (W.shift "web/irc")]
                    <+> manageDocks  -- manage xmobar, uses ManageDocks
         , layoutHook = avoidStruts (tiled ||| Mirror tiled ||| Full) }

tiled :: Tall a
tiled = Tall 1 (3/100) (1/2)

xpc :: XPConfig
xpc = defaultXPConfig { bgColor  = "black"
                      , fgColor  = "grey"
                      , promptBorderWidth = 0
                      , position = Bottom
                      , height   = 15
                      , historySize = 256 }
 
myKeys c = mkKeymap c $                                 -- keys; uses EZConfig
    [ ("M-S-<Return>",  spawn $ XMonad.terminal c)       -- spawn terminal
    , ("M-p"         ,  shellPrompt xpc)                 -- spawn menu program, uses Shell
    , ("M-s"         ,  search)                          -- search websites, uses Search & Submap
    , ("M-S-s"       ,  sshPrompt xpc)                   -- spawn ssh, uses Ssh
    , ("M-S-c"       ,  kill)                            -- kill window
    , ("M-<Space>"   ,  sendMessage NextLayout)          -- next layout
    , ("M-S-<Space>" ,  setLayout $ XMonad.layoutHook c) -- default layout
    , ("M-n"         ,  refresh)                         -- resize to correct size
    , ("M-j"         ,  windows W.focusDown)             -- move focus; next window
    , ("M-k"         ,  windows W.focusUp)               -- move focus; prev. window
    , ("M-m"         ,  windows W.focusMaster)           -- focus on master
    , ("M-<Return>"  ,  windows W.swapMaster)            -- swap current with master
    , ("M-S-j"       ,  windows W.swapDown)              -- swap focused with next window
    , ("M-S-k"       ,  windows W.swapUp)                -- swap focused with prev. window
    , ("M-h"         ,  sendMessage Shrink)              -- shrink master area
    , ("M-l"         ,  sendMessage Expand)              -- expand master area
    , ("M-t"         ,  withFocused $ windows . W.sink)  -- put window back on tiling layer
    , ("M-,"         ,  sendMessage (IncMasterN 1))      -- increase number of windows in master pane
    , ("M-."         ,  sendMessage (IncMasterN (-1)))   -- decrease number of windows in master pane
    , ("M-b"         ,  sendMessage ToggleStruts)        -- toggle status bar gap, uses ManageDocks
    , ("M-S-q"       ,  broadcastMessage ReleaseResources
                        >> restart "xmonad" True)        -- restart xmonad
    , ("C-S-q"       ,  io (exitWith ExitSuccess))       -- exit xmonad
    ] ++
    -- mod-[1..9], Switch to workspace N
    -- mod-shift-[1..9], Move client to workspace N
    [(m ++ k, windows $ f w)
        | (w, k) <- zip (XMonad.workspaces c) (map show [1..9])
        , (m, f) <- [("M-",W.greedyView), ("M-S-",W.shift)]]

 where searchSite = S.promptSearchBrowser xpc "ff3"
       search     = SM.submap . mkKeymap c $
                     [("g", searchSite S.google)
                     ,("h", searchSite S.hoogle)
                     ,("a", searchSite S.amazon)
                     ,("i", searchSite S.imdb)
                     ,("y", searchSite S.youtube)]