Advertisement
Not a member of Pastebin yet?
Sign Up,
it unlocks many cool features!
- -- xmonad.hs
- -- Author: sujoy `binarycodes` <[email protected]>
- --
- -- Last Modified: 4th January, 2009
- --
- -------------------------------------------------------------------------------
- -- Imports --
- -- stuff
- import XMonad
- import qualified XMonad.StackSet as W
- import qualified Data.Map as M
- import Data.Ratio ((%))
- import System.Exit
- import System.IO (Handle, hPutStrLn)
- -- utils
- import XMonad.Util.Run (spawnPipe)
- -- hooks
- import XMonad.Hooks.ManageDocks
- import XMonad.Hooks.DynamicLog
- import XMonad.Hooks.UrgencyHook
- import XMonad.ManageHook
- -- layouts
- import XMonad.Layout.NoBorders
- import XMonad.Layout.ResizableTile
- import XMonad.Layout.Tabbed
- import XMonad.Layout.Grid
- import XMonad.Layout.PerWorkspace (onWorkspace)
- import XMonad.Layout.IM
- import XMonad.Layout.ThreeColumns
- import XMonad.Layout.SimplestFloat
- -------------------------------------------------------------------------------
- -- Main --
- main = do
- h <- spawnPipe "xmobar"
- xmonad $ withUrgencyHook NoUrgencyHook
- $ defaultConfig
- { workspaces = workspaces'
- , modMask = modMask'
- , borderWidth = borderWidth'
- , normalBorderColor = normalBorderColor'
- , focusedBorderColor = focusedBorderColor'
- , terminal = terminal'
- , keys = keys'
- , logHook = logHook' h
- , layoutHook = layoutHook'
- , manageHook = manageHook'
- }
- -------------------------------------------------------------------------------
- -- Hooks --
- manageHook' :: ManageHook
- manageHook' = myManageHook <+> manageHook defaultConfig <+> manageDocks <+> (doF W.swapDown)
- myManageHook = composeAll $ concat
- [ [ stringProperty "WM_WINDOW_ROLE" =? roleC --> doIgnore | roleC <- hide ]
- , [ className =? webC --> doF (W.shift $ getWorkspaceId "web") | webC <- web ]
- , [ className =? mailC --> doF (W.shift $ getWorkspaceId "mail") | mailC <- mail ]
- , [ className =? docC --> doF (W.shift $ getWorkspaceId "doc") | docC <- doc ]
- , [ className =? codeC --> doF (W.shift $ getWorkspaceId "code") | codeC <- code ]
- , [ className =? chatC --> doF (W.shift $ getWorkspaceId "chat") | chatC <- chat ]
- , [ className =? multC --> doF (W.shift $ getWorkspaceId "mult") | multC <- mult ]
- , [ className =? downC --> doF (W.shift $ getWorkspaceId "down") | downC <- down ]
- ]
- where web = [ "Gran Paradiso", "Opera", "Firefox", "Kazehakase" ]
- doc = [ "GV" ,"Evince", "Xchm" ]
- code = [ ]
- chat = [ "Pidgin" ]
- mult = [ "Gimp" , "Blender" ]
- mail = [ "Thunderbird-bin", "Liferea-bin" ]
- down = [ "Transmission", "Deluge" ]
- hide = [ ]
- logHook' :: Handle -> X ()
- logHook' h = dynamicLogWithPP $ customPP { ppOutput = hPutStrLn h }
- layoutHook' = customLayout
- -------------------------------------------------------------------------------
- -- Looks --
- -- bar
- customPP :: PP
- customPP = defaultPP { ppCurrent = xmobarColor "#71BEBE" ""
- , ppTitle = shorten 80
- , ppSep = "<fc=#EFE58B> | </fc>"
- , ppUrgent = wrap "<fc=#FF0000>*</fc>" "<fc=#FF0000>*</fc>"
- , ppHidden = xmobarColor "#A5DCA5" ""
- , ppHiddenNoWindows = xmobarColor "#C4C4C4" ""
- }
- -- borders
- borderWidth' :: Dimension
- borderWidth' = 1
- normalBorderColor', focusedBorderColor' :: String
- normalBorderColor' = "#222222"
- focusedBorderColor' = "#222222"
- -- workspaces
- workspaceNames :: [String]
- workspaceNames = [ "main", "web", "chat", "doc", "code", "mail", "mult", "down" ]
- workspaces' :: [WorkspaceId]
- workspaces' = zipWith (++) (map show [1..]) wsnames
- where wsnames = map((:) ':') workspaceNames
- getWorkspaceId :: String -> WorkspaceId
- getWorkspaceId name = case lookup name (zip workspaceNames workspaces') of
- Just wsId -> wsId
- Nothing -> head workspaces'
- -- layouts
- customLayout = onWorkspace (getWorkspaceId "main") mainL
- $ onWorkspace (getWorkspaceId "web") webL
- $ onWorkspace (getWorkspaceId "doc") docL
- $ onWorkspace (getWorkspaceId "chat") chatL
- $ onWorkspace (getWorkspaceId "code") codeL
- $ onWorkspace (getWorkspaceId "mult") multL
- $ restL
- where tiled = ResizableTall 1 (2/100) (1/2) []
- threeCol = ThreeCol 1 (3/100) (1/2)
- im = avoidStruts $ IM ration roster
- ration = 1%5
- roster = And (ClassName "Pidgin") (Role "buddy_list")
- --roster = Title "Pidgin"
- mainL = avoidStruts $ smartBorders (tiled ||| Grid ||| Mirror tiled ||| simpleTabbedBottom ||| Full)
- webL = avoidStruts $ smartBorders (Full ||| Mirror tiled ||| tiled ||| simpleTabbedBottom)
- docL = avoidStruts $ smartBorders (Mirror tiled ||| tiled ||| Full ||| simpleTabbedBottom)
- codeL = avoidStruts $ smartBorders (tiled ||| Mirror tiled ||| Full ||| Grid)
- chatL = avoidStruts $ smartBorders (im ||| threeCol ||| Mirror tiled ||| tiled)
- multL = avoidStruts $ smartBorders (simplestFloat ||| threeCol ||| Mirror tiled ||| tiled)
- restL = avoidStruts $ smartBorders (tiled ||| Full ||| Grid ||| threeCol ||| simplestFloat)
- -------------------------------------------------------------------------------
- -- Terminal --
- terminal' :: String
- terminal' = "urxvtc"
- -- Dmenu stuffs --
- myBarFont :: String
- myBarFont = "-*-profont-*-*-*-*-11-*-*-*-*-*-*-*"
- myFocsFG, myFocsBG :: String
- myFocsFG = "#000000" -- focused foreground colour
- myFocsBG = "#999999" -- focused background colour
- myNormFG, myNormBG :: String
- myNormFG = "#8ba574" -- normal foreground colour
- myNormBG = "#000000" -- normal background colour
- myDmenuCmd :: String
- myDmenuCmd = "dmenu_path | dmenu -i -p 'Run:'" ++ myDmenuOpts
- where myDmenuOpts = concatMap ((:) ' '. (:) '-')
- [ wrap "nf '" "'" myNormFG
- , wrap "nb '" "'" myNormBG
- , wrap "sf '" "'" myFocsFG
- , wrap "sb '" "'" myFocsBG
- , wrap "fn '" "'" myBarFont ]
- -------------------------------------------------------------------------------
- -- Keys/Button bindings --
- -- modmask
- modMask' :: KeyMask
- modMask' = mod4Mask
- -- keys
- keys' :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
- keys' conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
- -- launching and killing programs
- [ --((modMask, xK_Return), spawn $ XMonad.terminal conf)
- ((modMask, xK_p ), spawn $ "exe=`" ++ myDmenuCmd ++ "` && eval \"exec $exe\"")
- --, ((modMask, xK_F2 ), spawn "gmrun")
- , ((modMask .|. shiftMask, xK_c ), kill)
- --, ((modMask .|. shiftMask, xK_m ), spawn "thunderbird")
- --, ((modMask, xK_f ), spawn "firefox")
- --, ((modMask .|. shiftMask, xK_p ), spawn "pidgin")
- --, ((modMask, xK_o ), spawn "opera")
- --, ((modMask, xK_w ), spawn "/usr/lib/wicd/gui.py")
- --, ((modMask, xK_e ), spawn "urxvtc -e emacs -nw")
- -- layouts
- , ((modMask, xK_space ), sendMessage NextLayout)
- , ((modMask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
- , ((modMask, xK_b ), sendMessage ToggleStruts)
- -- floating layer stuff
- , ((modMask, xK_t ), withFocused $ windows . W.sink)
- -- refresh
- , ((modMask, xK_n ), refresh)
- -- focus
- , ((modMask, xK_Tab ), windows W.focusDown)
- , ((modMask, xK_j ), windows W.focusDown)
- , ((modMask, xK_k ), windows W.focusUp)
- , ((modMask, xK_m ), windows W.focusMaster)
- -- swapping
- , ((modMask .|. shiftMask, xK_Return), windows W.swapMaster)
- , ((modMask .|. shiftMask, xK_j ), windows W.swapDown )
- , ((modMask .|. shiftMask, xK_k ), windows W.swapUp )
- -- increase or decrease number of windows in the master area
- , ((modMask , xK_comma ), sendMessage (IncMasterN 1))
- , ((modMask , xK_period), sendMessage (IncMasterN (-1)))
- -- resizing
- , ((modMask, xK_h ), sendMessage Shrink)
- , ((modMask, xK_l ), sendMessage Expand)
- , ((modMask .|. shiftMask, xK_h ), sendMessage MirrorShrink)
- , ((modMask .|. shiftMask, xK_l ), sendMessage MirrorExpand)
- -- quit, or restart
- , ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
- , ((modMask , xK_q ), restart "xmonad" True)
- ]
- ++
- -- mod-[1..9] %! Switch to workspace N
- -- mod-shift-[1..9] %! Move client to workspace N
- [((m .|. modMask, k), windows $ f i)
- | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
- , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
- -------------------------------------------------------------------------------
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement