[xmonad] Ratpoison key emulation

Gwern Branwen gwern0 at gmail.com
Sun Jun 29 08:38:57 EDT 2008


Hiya everyone. So as I've long mused about, I've gotten around to seeing how difficult it'd be to do a Ratpoison style keymap for XMonad. It went reasonably well, but I've run into a number of Ratpoison commands where I can't see what to bind them to (or whether the functionality is implemented in XMC somewhere I just don't know about), so I thought I'd demonstrate what I have and see whether anyone has any suggestions.

The code is as follows:


{- Not implemented:

C-t C-t
    Switch to the last window.
C-t t
    Sometimes you need to send a C-t to the current window. This keystroke does just that.

C-t A

C-t C-A
    Rename the current window. The window's new name will prevail for the rest of its lifetime.
C-t '

C-t C-'
    Go to a window by name. You will usually only need to type the first few characters of the window name.
C-t a

C-t C-a
    Display the current time of day.

C-t :
    This allows you to execute a single ratpoison command.
C-t i

C-t C-i
    Display information about the current window.

C-t m

C-t C-m
    Display the last message.
C-t V

C-t C-V
    Display ratpoison's license.

C-t w

C-t C-w
    Display the list of managed windows. The current window is highlighted.

C-t M-tab
    Switch to the last focused frame.
C-t Q
    Kill all frames but the current one.
C-t R
    Kill the current frame. This is a no-op if there is only one frame.
C-t r

C-t C-r
    Resize the current frame.

C-t ?
    Display a help screen.
C-t f

C-t C-f
    select a frame by number.
C-t F
    Indicate which frame is the current frame.
C-t x

C-t C-x
    Choose a frame and exchange the window in the current frame with the window in the chosen frame.
-}
-- | This list, duplicates and all is based off of
-- <http://www.nongnu.org/ratpoison/doc/Default-Key-Bindings.html#Default Key Bindings>.
ratpoisonKeys :: XConfig t -> Map (KeyMask, KeySym) (X ())
ratpoisonKeys conf@(XConfig {XMonad.modMask = m}) = M.fromList $ [ -- rebind standard
                                                                   -- actions
            -- this defines our root-key - mod-t
            ((m, xK_t),  submap . M.fromList $
                          -- OK, now we can begin to list all
                          -- the actual Ratpoison bindings
                          -- which live in this submap.
                          [ ((0, xK_n),     next)
                          , ((m, xK_n),     next)
                          , ((0, xK_space), next)
                          , ((m, xK_space), next)
                          , ((0, xK_Return), next)
                          , ((m, xK_Return), next)

                          , ((0, xK_p),     previous)
                          , ((m, xK_p),     previous)

                          , ((0, xK_k), kill)
                          , ((m, xK_k), kill)
                          , ((0, xK_K), kill)
                          , ((m, xK_K), kill)

                          , ((0, xK_c), spawn term)
                          , ((m, xK_c), spawn term)

                          , ((m, xK_exclam), prompt (term ++ " -e") defaultXPConfig)
                          , ((0, xK_exclam), prompt ("/bin/sh" ++ " -c") defaultXPConfig)

                          -- We call out to the shell because
                          -- we can't use Main.hs's trick of
                          -- "showVersion version" - we don't
                          -- see Paths_xmonad
                          , ((0, xK_v), version)
                          , ((m, xK_v), version)

                          , ((0, xK_l), refresh)
                          , ((m, xK_l), refresh)

                          -- This is wrong.
                          , ((0, xK_s), sendMessage NextLayout)
                          , ((m, xK_s), sendMessage NextLayout)
                          , ((0 .|. shiftMask, xK_s), sendMessage NextLayout)
                          , ((m .|. shiftMask, xK_s), sendMessage NextLayout)

                          , ((0, xK_b), banish)
                          , ((m, xK_b), banish)

                          , ((0, xK_Right), sendMessage $ Go R)
                          , ((0, xK_Left ), sendMessage $ Go L)
                          , ((0, xK_Up   ), sendMessage $ Go U)
                          , ((0, xK_Down ), sendMessage $ Go D)
                          , ((m, xK_Right), sendMessage $ Swap R)
                          , ((m, xK_Left ), sendMessage $ Swap L)
                          , ((m, xK_Up   ), sendMessage $ Swap U)
                          , ((m, xK_Down ), sendMessage $ Swap D)
                          ] ++
             [((0, k), windows $ f i)
                  | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
             , (f, _) <- [(W.greedyView, 0), (W.shift, shiftMask)]]

            )]
                  where
                       next = windows W.focusDown
                       previous = windows W.focusUp
                       term = XMonad.terminal conf
                       version = spawn "xmessage `xmonad --version`"
                       banish :: X ()
                       banish = warpToWindow 1 1 -- lower right


--
gwern
Al E.O.D. Freedom Inmarsat 6 B43 ^X STARLAN FOSS NSRB
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/xmonad/attachments/20080629/a9d9c0dc/attachment.bin


More information about the xmonad mailing list