Difference between revisions of "Xmonad/Config archive/twifkak's Config.hs"

From HaskellWiki
Jump to navigation Jump to search
(re-comment to highlight the differences)
 
(4 intermediate revisions by one other user not shown)
Line 1: Line 1:
  +
Things that are no different from standard are commented out to make it easier to scan for the interesting bits. Removed type signatures for the same reason. Obviously, neither is the case in my real Config.hs. ;)
  +
 
<haskell>
 
<haskell>
  +
{-
-- Changes denoted by -- START DLM/-- END DLM. Everything else is out
 
-- of the box. OOTB comments removed.
 
 
module Config where
 
module Config where
   
Line 12: Line 13:
 
import System.Exit
 
import System.Exit
 
import Graphics.X11.Xlib
 
import Graphics.X11.Xlib
  +
-}
   
-- START DLM
 
 
import XMonadContrib.Dzen
 
import XMonadContrib.Dzen
 
import XMonadContrib.NoBorders
 
import XMonadContrib.NoBorders
Line 24: Line 25:
   
 
-- Added workspace zero. Really, should append it to the end, as xmonad starts in `head workspaces`.
 
-- Added workspace zero. Really, should append it to the end, as xmonad starts in `head workspaces`.
workspaces :: [WorkspaceId]
 
 
workspaces = map show [0 .. 9 :: Int]
 
workspaces = map show [0 .. 9 :: Int]
   
 
-- mod4 == apple/cmd key for me (per xmodmap)
 
-- mod4 == apple/cmd key for me (per xmodmap)
modMask :: KeyMask
 
 
modMask = mod4Mask
 
modMask = mod4Mask
   
 
-- apple doesn't have a numlock key
 
-- apple doesn't have a numlock key
numlockMask :: KeyMask
 
 
numlockMask = 0
 
numlockMask = 0
   
  +
{-
-- END DLM
 
 
 
borderWidth :: Dimension
 
borderWidth :: Dimension
 
borderWidth = 1
 
borderWidth = 1
Line 55: Line 52:
 
manageHook _ _ "Gecko" _ = return $ W.shift "web"
 
manageHook _ _ "Gecko" _ = return $ W.shift "web"
 
manageHook _ _ _ _ = return id
 
manageHook _ _ _ _ = return id
  +
-}
 
-- START DLM
 
   
 
-- | Normal window managers respond to windows setting the UrgencyHint by
 
-- | Normal window managers respond to windows setting the UrgencyHint by
Line 64: Line 60:
   
 
-- Replace Full with noBorders tabbed.
 
-- Replace Full with noBorders tabbed.
layouts :: [Layout Window]
 
 
layouts = [ Layout tiled
 
layouts = [ Layout tiled
 
, Layout $ Mirror tiled
 
, Layout $ Mirror tiled
Line 70: Line 65:
 
]
 
]
 
where
 
where
  +
-- The standard definition.
 
tiled = Tall nmaster delta ratio
 
tiled = Tall nmaster delta ratio
 
nmaster = 1
 
nmaster = 1
Line 78: Line 74:
 
-- configurableNavigation noNavigateBorders lets me use a/w/s/d to navigate
 
-- configurableNavigation noNavigateBorders lets me use a/w/s/d to navigate
 
-- windows orthographically (esp. since I'm in a 2x2 grid often).
 
-- windows orthographically (esp. since I'm in a 2x2 grid often).
layoutHook :: Layout Window
 
 
layoutHook = Layout $ withUrgencyHook $ configurableNavigation noNavigateBorders $ Select layouts
 
layoutHook = Layout $ withUrgencyHook $ configurableNavigation noNavigateBorders $ Select layouts
   
  +
{-
-- END DLM
 
 
serialisedLayouts :: [Layout Window]
 
 
serialisedLayouts = layoutHook : layouts
 
serialisedLayouts = layoutHook : layouts
logHook :: X ()
 
 
logHook = return ()
 
logHook = return ()
  +
-}
   
keys :: M.Map (KeyMask, KeySym) (X ())
 
 
keys = M.fromList $
 
keys = M.fromList $
 
[ ((modMask .|. shiftMask, xK_Return), spawn "urxvt") -- urxvt instead of xterm
-- START DLM
 
[ ((modMask .|. shiftMask, xK_Return), spawn "rxvt") -- rxvt instead of xterm
 
 
, ((modMask .|. shiftMask, xK_d ), spawn "(date; sleep 2) | dzen2") -- %! Print current date
 
, ((modMask .|. shiftMask, xK_d ), spawn "(date; sleep 2) | dzen2") -- %! Print current date
-- END DLM
 
   
  +
{-
 
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu
 
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu
 
, ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window
 
, ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window
Line 115: Line 106:
 
, ((modMask.|.controlMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
 
, ((modMask.|.controlMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
 
, ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad
 
, ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad
  +
-}
   
-- START DLM
 
 
-- RotView cycles between non-empty workspaces -- i/o equals "left"/"right"
 
-- RotView cycles between non-empty workspaces -- i/o equals "left"/"right"
 
-- along the number keys.
 
-- along the number keys.
Line 129: Line 120:
 
, ((modMask .|. shiftMask, xK_g ), gotoMenu)
 
, ((modMask .|. shiftMask, xK_g ), gotoMenu)
 
, ((modMask .|. shiftMask, xK_b ), bringMenu)
 
, ((modMask .|. shiftMask, xK_b ), bringMenu)
-- END DLM
 
 
]
 
]
  +
{-
 
++
 
++
 
[((m .|. modMask, k), windows $ f i)
 
[((m .|. modMask, k), windows $ f i)
 
| (i, k) <- zip workspaces [xK_0 .. xK_9]
 
| (i, k) <- zip workspaces [xK_0 .. xK_9]
 
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
 
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
  +
-}
-- START DLM
 
  +
 
-- I don't have multiple screens, so I free up mod{-shift,}-{w,e,r} by
 
-- I don't have multiple screens, so I free up mod{-shift,}-{w,e,r} by
 
-- removing those mappings. (Used in the above Workspace navigation definition.)
 
-- removing those mappings. (Used in the above Workspace navigation definition.)
Line 156: Line 148:
 
, ((controlMask .|. shiftMask, button3), (\w -> focus w >> mouseResizeWindow w))
 
, ((controlMask .|. shiftMask, button3), (\w -> focus w >> mouseResizeWindow w))
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
-- END DLM
 
 
]
 
]
 
</haskell>
 
</haskell>
  +
  +
[[Category:XMonad configuration]]

Latest revision as of 21:56, 6 November 2007

Things that are no different from standard are commented out to make it easier to scan for the interesting bits. Removed type signatures for the same reason. Obviously, neither is the case in my real Config.hs. ;)

{-
module Config where

import XMonad
import Operations
import qualified StackSet as W
import Data.Ratio
import Data.Bits ((.|.))
import qualified Data.Map as M
import System.Exit
import Graphics.X11.Xlib
-}

import XMonadContrib.Dzen
import XMonadContrib.NoBorders
import XMonadContrib.RotView
import XMonadContrib.SwapWorkspaces
import XMonadContrib.Tabbed
import XMonadContrib.UrgencyHook
import XMonadContrib.WindowBringer
import XMonadContrib.WindowNavigation

-- Added workspace zero. Really, should append it to the end, as xmonad starts in `head workspaces`.
workspaces = map show [0 .. 9 :: Int]

-- mod4 == apple/cmd key for me (per xmodmap)
modMask = mod4Mask

-- apple doesn't have a numlock key
numlockMask = 0

{-
borderWidth :: Dimension
borderWidth = 1
normalBorderColor, focusedBorderColor :: String
normalBorderColor  = "#dddddd"
focusedBorderColor = "#ff0000"
defaultGaps :: [(Int,Int,Int,Int)]
defaultGaps = [(0,0,0,0)] -- 15 for default dzen font
manageHook :: Window -- ^ the new window to manage
           -> String -- ^ window title
           -> String -- ^ window resource name
           -> String -- ^ window resource class
           -> X (WindowSet -> WindowSet)
manageHook w _ _ c | c `elem` floats = fmap (W.float w . snd) (floatLocation w)
 where floats = ["MPlayer", "Gimp"]
manageHook w _ n _ | n `elem` ignore = reveal w >> return (W.delete w)
 where ignore = ["gnome-panel", "desktop_window", "kicker", "kdesktop"]
manageHook _ _ "Gecko" _ = return $ W.shift "web"
manageHook _ _ _ _ = return id
-}

-- | Normal window managers respond to windows setting the UrgencyHint by
-- flashing the taskbar. Here, I throw up a dzen, "Xchat is requesting your attention yada yada."
urgencyHook :: Window -> X ()
urgencyHook = dzenUrgencyHook (5 `seconds`)

-- Replace Full with noBorders tabbed.
layouts = [ Layout tiled
          , Layout $ Mirror tiled
          , Layout $ noBorders $ tabbed shrinkText defaultTConf
          ]
  where
     -- The standard definition.
     tiled   = Tall nmaster delta ratio
     nmaster = 1
     ratio   = 1%2
     delta   = 3%100

-- withUrgencyHook catches the urgency events from X clients.
-- configurableNavigation noNavigateBorders lets me use a/w/s/d to navigate
-- windows orthographically (esp. since I'm in a 2x2 grid often).
layoutHook = Layout $ withUrgencyHook $ configurableNavigation noNavigateBorders $ Select layouts

{-
serialisedLayouts = layoutHook : layouts
logHook = return ()
-}

keys = M.fromList $
    [ ((modMask .|. shiftMask, xK_Return), spawn "urxvt") -- urxvt instead of xterm
    , ((modMask .|. shiftMask, xK_d     ), spawn "(date; sleep 2) | dzen2") -- %! Print current date

{-
    , ((modMask,               xK_p     ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu
    , ((modMask .|. shiftMask, xK_c     ), kill) -- %! Close the focused window
    , ((modMask,               xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms
    , ((modMask .|. shiftMask, xK_space ), setLayout layoutHook) -- %!  Reset the layouts on the current workspace to default
    , ((modMask,               xK_n     ), refresh) -- %! Resize viewed windows to the correct size
    , ((modMask,               xK_Tab   ), windows W.focusDown) -- %! Move focus to the next window
    , ((modMask,               xK_j     ), windows W.focusDown) -- %! Move focus to the next window
    , ((modMask,               xK_k     ), windows W.focusUp  ) -- %! Move focus to the previous window
    , ((modMask,               xK_m     ), windows W.focusMaster  ) -- %! Move focus to the master window
    , ((modMask,               xK_Return), windows W.swapMaster) -- %! Swap the focused window and the master window
    , ((modMask .|. shiftMask, xK_j     ), windows W.swapDown  ) -- %! Swap the focused window with the next window
    , ((modMask .|. shiftMask, xK_k     ), windows W.swapUp    ) -- %! Swap the focused window with the previous window
    , ((modMask,               xK_h     ), sendMessage Shrink) -- %! Shrink the master area
    , ((modMask,               xK_l     ), sendMessage Expand) -- %! Expand the master area
    , ((modMask,               xK_t     ), withFocused $ windows . W.sink) -- %! Push window back into tiling
    , ((modMask              , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
    , ((modMask              , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
    , ((modMask              , xK_b     ), modifyGap (\i n -> let x = (defaultGaps ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
    , ((modMask.|.controlMask, xK_q     ), io (exitWith ExitSuccess)) -- %! Quit xmonad
    , ((modMask              , xK_q     ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad
-}

-- RotView cycles between non-empty workspaces -- i/o equals "left"/"right"
-- along the number keys.
    , ((modMask              , xK_i     ), rotView False)
    , ((modMask              , xK_o     ), rotView True)
-- Workspace navigation as set up in the layoutHooks definition.
    , ((modMask,               xK_a     ), sendMessage $ Go L)
    , ((modMask,               xK_w     ), sendMessage $ Go U)
    , ((modMask,               xK_s     ), sendMessage $ Go D)
    , ((modMask,               xK_d     ), sendMessage $ Go R)
-- WindowBringer -- type the title of a window to jump to it or grab it.
    , ((modMask .|. shiftMask, xK_g     ), gotoMenu)
    , ((modMask .|. shiftMask, xK_b     ), bringMenu)
    ]
{-
    ++
    [((m .|. modMask, k), windows $ f i)
        | (i, k) <- zip workspaces [xK_0 .. xK_9]
        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
-}

-- I don't have multiple screens, so I free up mod{-shift,}-{w,e,r} by
-- removing those mappings. (Used in the above Workspace navigation definition.)

-- Alt-Apple-Number swaps the current workspace with the numbered one.
-- A simple way to move collections of windows at once.
    ++
    [((modMask .|. mod1Mask, k), windows $ swapWithCurrent i)
        | (i, k) <- zip workspaces [xK_0 ..]]

-- Change modMask to controlMask .|. shiftMask, since Apple translates
-- Apple-Click into Right-Click.
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
mouseBindings = M.fromList $
    -- mod-button1 %! Set the window to floating mode and move by dragging
    [ ((controlMask .|. shiftMask, button1), (\w -> focus w >> mouseMoveWindow w))
    -- mod-button2 %! Raise the window to the top of the stack
    , ((controlMask .|. shiftMask, button2), (\w -> focus w >> windows W.swapMaster))
    -- mod-button3 %! Set the window to floating mode and resize by dragging
    , ((controlMask .|. shiftMask, button3), (\w -> focus w >> mouseResizeWindow w))
    -- you may also bind events to the mouse scroll wheel (button4 and button5)
    ]