[xmonad] Bluetile

gwern0 at gmail.com gwern0 at gmail.com
Tue Aug 25 05:17:00 EDT 2009


Resources:

- Original thread/ANN: http://thread.gmane.org/gmane.comp.lang.haskell.xmonad/7458/
     - Jan Vorberger's OP: http://article.gmane.org/gmane.comp.lang.haskell.xmonad/7458

> "I'm planning to decide on a somewhat fixed configuration of XMonad, probably in combination with Gnome as a DE, and then trying to make this functionality available via mouse commands that - hopefully - will be easy to pick up.<br>
> I also want to completely rework the whole floating layer thing, as it seems to me to be a fairly foreing [sic] concept for a newcomer and it's awkward to use. My current idea is to instead use a floating layout algorithm, that could work similiar [sic] to a conventional window manager. It could even be set as the default layout algorithm. That way, the WM could almost be a 'drop-in' replacement for - let's say Metacity - greeting the user with the familiar concept of manipulating windows and then leading him to the tiling paradigm once he switches the layout."

Jan later [wrote](http://article.gmane.org/gmane.comp.lang.haskell.xmonad/7495) that

> "@Don: I will definitely try to contribute back changes and improvements, if I can. Once I start implementing I will also make my repository available for others to try out. Thx for offering assistance, I might come back to that later."

But given that Bluetile has been done a while, I guess we'll just have to content ourselves with the repos.

- A PDF presentation of some sort is available at http://parsys.informatik.uni-oldenburg.de/theses/docs/bluetile_zwischenvortrag.pdf
     - Google Translate link, may or may not work: http://translate.google.com/translate?hl=en&sl=de&u=http://parsys.informatik.uni-oldenburg.de/theses/docs/bluetile_zwischenvortrag.pdf

The actual code seems to be broken up into 4 packages; everything is BSD3 so no concerns about reuse:

- bluetilutils: http://hackage.haskell.org/package/bluetileutils (Darcs repo: http://tuvok.home.dyndns.org/bluetile-repos/bluetileutils down?)
     A package of 3 Gtk2hs executables:
       i. bluetiledock
       ii. bluetilemockwin
       iii. bluetilegreet
- xmonad-bluetilebranch: http://hackage.haskell.org/package/xmonad-bluetilebranch (I have no local repo for this, although it was presumably at http://tuvok.home.dyndns.org/bluetile-repos/xmonad-bluetilebranch )
- xmonad-contrib-bluetilebranch: http://hackage.haskell.org/package/xmonad-contrib-bluetilebranch (same comment for repo)
- bluetile: http://hackage.haskell.org/package/bluetile (repo: http://tuvok.home.dyndns.org/bluetile-repos/bluetile )

Now, looking at the code (bearing in mind I am only reading and haven't compiled/run anything yet):

# bluetileutils
## bluetiledock

This creates a minimalistic strut app. It supports 14 buttons/commands:

- switch to workspaces 0-9
- 4 commands to switch to floating/tiled1/tiled2/fullscreen (presumably tiled1 and tiled2 = 2 windows each on 1/2 screen split horizontal & vertical)

Interesting is how bluetiledock achieves this functionality, how it makes xmonad actually do something - it seems to be using a X-based method of IPC, in which a integer is stored in an X atom and xmonad then grabs it and does something with it:

~~~~{.haskell}
sendCommandX :: Int -> IO ()
sendCommandX com = do
  d   <- X.openDisplay ""
  rw  <- X.rootWindow d $ X.defaultScreen d
  a <- X.internAtom d "XMONAD_COMMAND" False
  X.allocaXEvent $ \e -> do
                  XE.setEventType e X.clientMessage
                  XE.setClientMessageEvent e rw a 32 (fromIntegral com) XE.currentTime
                  X.sendEvent d rw False X.structureNotifyMask e
                  X.sync d False
~~~~

## bluetilegreet

A splashscreen/help; checks for empty file ~/.bluetilegreet and if it exists, makes it and runs. It then basically displays the XML contents of bluetilegreet.glade, which run something like:

~~~~{.xml}
                    <property name="label" translatable="yes">Quickstart: Open a few windows and notice that you are currently in the traditional layout mode, known from most other window managers. To start tiling, switch to another layout in one of these ways:</property>
                    <property name="wrap">True</property>
                  </widget>
                </child>
                <child>
                  <widget class="GtkLabel" id="label3">
                    <property name="visible">True</property>
                    <property name="label" translatable="yes">* Using the dock on the left (buttons A, S, D or F),
* pressing the middle mouse button while
   holding down the Windows key or
* using the keyboard shortcuts Win+A, Win+S,
   Win+D or Win+F .</property>
                  </widget>
                  <packing>
                    <property name="top_attach">1</property>
                    <property name="bottom_attach">2</property>
                  </packing>
                </child>
                <child>
                  <widget class="GtkLabel" id="label4">
                    <property name="visible">True</property>
                    <property name="label" translatable="yes">You should be fine exploring the tiling paradigm with your mouse alone, but to get the most out of it you might want to look at the keyboard shortcuts at some point. They are documented on Bluetile's website.</property>
                    <property name="wrap">True</property>
~~~~

It might be a good idea to have something similar for XMonad; it's not like it really matters if we dump an empty hidden file in ~/.xmonad

## bluetilemockwin

No idea. It creates some sort of widget with the RGB color specified as 3 ints. Grep doesn't seem to show up any use in the main bluetile repo.

~~~~{.haskell}
main :: IO ()
main = do
    args <- getArgs
    progName <- getProgName
    if length args /= 3
        then putStrLn $ "Usage: " ++ progName ++ " 0 0 65535"
        else let r = read $ args !! 0
                 g = read $ args !! 1
                 b = read $ args !! 2
             in showMockWin (Color r g b)

showMockWin :: Color -> IO ()
showMockWin c = do
    initGUI
    window <- windowNew
    onDestroy window mainQuit
    widgetModifyBg window StateNormal c
    widgetShowAll window
    mainGUI
~~~~

# xmonad-contrib-bluetilebranch

Without a repo, it's hard to know exactly what's changed. But by my count, this XMC fork adds the following modules:

- XMonad.Actions.BluetileCommands
    defines `[(String, X ())]`, which seem to support the 14 commands used by the dock, and 4 others (quit, quit-and-start-metacity, increase master, decrease master)
- XMonad.Actions.WindowMenu
     much as it sounds, supporting the following commands:

~~~~{.haskell}
        actions = [ ("Cancel menu", return ())
                  , ("Close"      , kill)
                  , ("Maximize"   , sendMessage $ maximizeRestore w)
                  , ("Minimize"   , sendMessage $ MinimizeWin w)
                  ] ++
                  [ ("Move to workspace " ++ tag, windows $ W.shift tag)
                    | tag <- tags ]
~~~~

- XMonad.Hooks.BluetileDock
- XMonad.Hooks.CustomRestart
     adequately summarized by a snippet

~~~~{.haskell}
        a <- io $ internAtom d "XMONAD_CUSTOM_RESTART" False
        when (mt == a) $ do
            restart prog True
~~~~

- XMonad.Hooks.EventHook
     Old code? Seems to've been removed in darcs XMC
- XMonad.Hooks.RestoreMinimized
- XMonad.Hooks.WorkspaceByPos
     No idea. What I did notice is that it looks like it could use the Maybe monad!
~~~{.haskell}
needsMoving :: Window -> X (Maybe WorkspaceId)
needsMoving w = withDisplay $ \d -> do
                    -- only relocate windows with non-zero position
                    wa <- io $ getWindowAttributes d w
                    if ((wa_x wa) == 0) && ((wa_y wa) == 0)
                        then return Nothing
                        else do
                            ws <- gets windowset
                            sc <- fromMaybe (W.current ws)
                                    <$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
                            maybeWkspc <- screenWorkspace (W.screen sc)
                            case maybeWkspc of
                                Nothing -> return Nothing
                                Just wkspc -> do
                                    let currentWksp = W.currentTag ws
                                    if currentWksp == wkspc
                                        then return Nothing
                                        else return (Just wkspc)
~~~~

- XMonad.Layout.BorderResize
- XMonad.Layout.DecorationUtils
     Support for the BorderResize?
- XMonad.Layout.DraggingVisualizer
- XMonad.Layout.MouseResizableTile
- XMonad.Layout.NoFrillsDecoration
- XMonad.Layout.PositionStoreFloat
- XMonad.Layout.ThreeColumnsMiddle
     just an alias for ThreeColumns
- XMonad.Layout.WindowSwitcherDecoration
    looks like a module to use a mouse to 'drag' a window onto another and swap their positions

# bluetile

About what you would expect - importing most of the above, running the dock and the greeter.

So to conclude this whirlwind tour: I see a lot of valuable stuff.

The greeter is something that could definitely be in core (although I think the gtk2hs dep is untenable, so I expect a better idea would be to run an xmessage prompt with a list of keybindings). The dock is a nice alternative to the ridiculously baroque setups for xmobar and dzen - those may be really nice and customizable, but they are absolutely unsuitable for beginners, and even setting up a Gnome panel is a bit much for non-intermediate or advanced XMonaders.

And the string atom stuff has already been done by Stumpwm/Ratpoison, and I asked for this in the past - XMonad should be scriptable from the outside.

-- 
gwern
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 197 bytes
Desc: OpenPGP digital signature
Url : http://www.haskell.org/pipermail/xmonad/attachments/20090825/8f0992be/signature.bin


More information about the xmonad mailing list