mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
focus left and right (mod-j/mod-k)
This commit is contained in:
parent
ac09d64e06
commit
e531be5476
65
Main.hs
65
Main.hs
@ -67,7 +67,9 @@ keys =
|
|||||||
[ (mod1Mask .|. shiftMask, xK_Return, spawn "xterm")
|
[ (mod1Mask .|. shiftMask, xK_Return, spawn "xterm")
|
||||||
, (mod1Mask, xK_p, spawn "exe=`dmenu_path | dmenu` && exec $exe")
|
, (mod1Mask, xK_p, spawn "exe=`dmenu_path | dmenu` && exec $exe")
|
||||||
, (controlMask, xK_space, spawn "gmrun")
|
, (controlMask, xK_space, spawn "gmrun")
|
||||||
, (mod1Mask, xK_Tab, switch)
|
, (mod1Mask, xK_Tab, focus 1)
|
||||||
|
, (mod1Mask, xK_j, focus 1)
|
||||||
|
, (mod1Mask, xK_k, focus (-1))
|
||||||
, (mod1Mask .|. shiftMask, xK_q, io $ exitWith ExitSuccess)
|
, (mod1Mask .|. shiftMask, xK_q, io $ exitWith ExitSuccess)
|
||||||
]
|
]
|
||||||
|
|
||||||
@ -112,63 +114,50 @@ handle _ = return ()
|
|||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Managing windows
|
-- Managing windows
|
||||||
|
|
||||||
|
--
|
||||||
|
-- | refresh. Refresh the currently focused window. Resizes to full
|
||||||
|
-- screen and raises the window.
|
||||||
|
--
|
||||||
|
refresh :: W ()
|
||||||
|
refresh = do
|
||||||
|
ws <- gets windows
|
||||||
|
case ws of
|
||||||
|
[] -> return ()
|
||||||
|
(w:_) -> do
|
||||||
|
d <- gets display
|
||||||
|
sw <- liftM fromIntegral (gets screenWidth)
|
||||||
|
sh <- liftM fromIntegral (gets screenHeight)
|
||||||
|
io $ do moveResizeWindow d w 0 0 sw sh
|
||||||
|
raiseWindow d w
|
||||||
|
|
||||||
-- | Modify the current window list with a pure funtion, and refresh
|
-- | Modify the current window list with a pure funtion, and refresh
|
||||||
withWindows :: (Windows -> Windows) -> W ()
|
withWindows :: (Windows -> Windows) -> W ()
|
||||||
withWindows f = do
|
withWindows f = do
|
||||||
modifyWindows f
|
modifyWindows f
|
||||||
refresh
|
refresh
|
||||||
|
|
||||||
-- | Run an action on the currently focused window
|
|
||||||
withCurrent :: (Window -> W ()) -> W ()
|
|
||||||
withCurrent f = do
|
|
||||||
ws <- gets windows
|
|
||||||
case ws of
|
|
||||||
[] -> return ()
|
|
||||||
(w:_) -> f w
|
|
||||||
|
|
||||||
--
|
|
||||||
-- | refresh. Refresh the currently focused window. Resizes to full
|
|
||||||
-- screen and raises the window.
|
|
||||||
--
|
|
||||||
refresh :: W ()
|
|
||||||
refresh = withCurrent $ \w -> do
|
|
||||||
d <- gets display
|
|
||||||
sw <- gets screenWidth
|
|
||||||
sh <- gets screenHeight
|
|
||||||
io $ do moveResizeWindow d w 0 0 (fromIntegral sw) (fromIntegral sh)
|
|
||||||
raiseWindow d w
|
|
||||||
|
|
||||||
--
|
|
||||||
-- | manage. Add a new window to be managed
|
-- | manage. Add a new window to be managed
|
||||||
--
|
|
||||||
manage :: Window -> W ()
|
manage :: Window -> W ()
|
||||||
manage w = do
|
manage w = do
|
||||||
trace "manage"
|
trace "manage"
|
||||||
d <- gets display
|
d <- gets display
|
||||||
withWindows $ \ws -> if w `elem` ws then ws else w:ws -- a set
|
withWindows (nub . (w :))
|
||||||
io $ mapWindow d w
|
io $ mapWindow d w
|
||||||
|
|
||||||
--
|
|
||||||
-- | unmanage, a window no longer exists, remove it from the stack
|
-- | unmanage, a window no longer exists, remove it from the stack
|
||||||
--
|
|
||||||
unmanage :: Window -> W ()
|
unmanage :: Window -> W ()
|
||||||
unmanage w = do
|
unmanage w = do
|
||||||
dpy <- gets display
|
dpy <- gets display
|
||||||
io $ grabServer dpy
|
io $ do grabServer dpy
|
||||||
modifyWindows (filter (/= w))
|
sync dpy False
|
||||||
io $ sync dpy False
|
ungrabServer dpy
|
||||||
io $ ungrabServer dpy
|
withWindows $ filter (/= w)
|
||||||
refresh
|
|
||||||
|
|
||||||
--
|
-- | focus. focus to window at offset 'n' in list.
|
||||||
-- | switch. switch focus to next window in list.
|
|
||||||
-- The currently focused window is always the head of the list
|
-- The currently focused window is always the head of the list
|
||||||
--
|
focus :: Int -> W ()
|
||||||
switch :: W ()
|
focus n = withWindows (rotate n)
|
||||||
switch = withWindows rotate
|
|
||||||
|
|
||||||
--
|
|
||||||
-- | spawn. Launch an external application
|
-- | spawn. Launch an external application
|
||||||
--
|
|
||||||
spawn :: String -> W ()
|
spawn :: String -> W ()
|
||||||
spawn = io_ . runCommand
|
spawn = io_ . runCommand
|
||||||
|
31
W.hs
31
W.hs
@ -29,6 +29,14 @@ data WState = WState
|
|||||||
, windows :: !Windows
|
, windows :: !Windows
|
||||||
}
|
}
|
||||||
|
|
||||||
|
--
|
||||||
|
-- Multithreaded issues:
|
||||||
|
--
|
||||||
|
-- We'll want a status bar, it will probably read from stdin
|
||||||
|
-- but will thus need to run in its own thread, and modify its status
|
||||||
|
-- bar window
|
||||||
|
--
|
||||||
|
|
||||||
type Windows = [Window]
|
type Windows = [Window]
|
||||||
|
|
||||||
-- | The W monad, a StateT transformer over IO encapuslating the window
|
-- | The W monad, a StateT transformer over IO encapuslating the window
|
||||||
@ -74,6 +82,23 @@ forever a = a >> forever a
|
|||||||
snoc :: [a] -> a -> [a]
|
snoc :: [a] -> a -> [a]
|
||||||
snoc xs x = xs ++ [x]
|
snoc xs x = xs ++ [x]
|
||||||
|
|
||||||
-- | Rotate a list one element
|
-- | Rotate a list by 'n' elements.
|
||||||
rotate [] = []
|
--
|
||||||
rotate (x:xs) = xs `snoc` x
|
-- for xs = [5..8] ++ [1..4]
|
||||||
|
--
|
||||||
|
-- rotate 0
|
||||||
|
-- [5,6,7,8,1,2,3,4]
|
||||||
|
--
|
||||||
|
-- rotate 1
|
||||||
|
-- [6,7,8,1,2,3,4,5]
|
||||||
|
--
|
||||||
|
-- rotate (-1)
|
||||||
|
-- [4,5,6,7,8,1,2,3]
|
||||||
|
--
|
||||||
|
rotate n xs = take l . drop offset . cycle $ xs
|
||||||
|
where
|
||||||
|
l = length xs
|
||||||
|
offset | n < 0 = l + n
|
||||||
|
| otherwise = n
|
||||||
|
|
||||||
|
|
||||||
|
Loading…
x
Reference in New Issue
Block a user