[xmonad] is it possible to display workspace number on the corresponding screen?

Don Stewart dons00 at gmail.com
Mon May 9 01:38:59 CEST 2011


Googling around, there are some examples. E.g.:

http://code.google.com/p/xmonad/issues/attachmentText?id=413&aid=-5265428714529951209&name=xmonad.hs&token=d4312fbc3743366f82e4e1cea9c9e540

defines some additional key bindings:

myKeys (XConfig {XMonad.modMask = modMask}) osd = M.fromList $
    [ ((modMask, xK_p), Shell.shellPrompt myXPConfig)
    , ((0, 0x1008ff11), volumeDown 1 >> showVolume osd)
    , ((0, 0x1008ff13), volumeUp 1 >> showVolume osd)
    , ((0, 0x1008ff12), toggleMute >> showVolume osd)
    , ((0, xK_Pause), spawn "lock_display")
    ]

in particular, it binds those first few key bindings to actions that call XOSD:

 getOffset :: X Int
getOffset = withWindowSet $ \W.StackSet {current=W.Screen
{screenDetail=SD {screenRect=Rectangle {rect_x=x}}}} -> return $
fromIntegral x

displayOsd osd msg =
    do
        xpos <- getOffset
        io $ set osd [HOffset xpos]
        io $ Graphics.XOSD.display osd 0 msg

showVolume :: XOSD -> X ()
showVolume osd =
    do
        volume <- io $ getCurrentVolume
        muted <- io $ getMutedState
        displayOsd osd $ Percent $ if muted then 0 else volume

I also had the following code lying around, that uses the `xosd`
binary that my library installs:

-- Programmatically, however, we probably should spawn the xosd binary.
-- Todo: try adding the workspace number too?
name :: X ()
name = do
    XState { windowset = ws } <- get
    let n = screen (current ws) -- show screen indicies.

    liftIO $ XOSD.runXOSD [ XOSD.Timeout 3
            , XOSD.VAlign XOSD.VAlignMiddle
            , XOSD.HAlign XOSD.HAlignCenter
            , XOSD.Font "-adobe-helvetica-bold-r-*-*-34-*-*-*-*-*-*-*"
            , XOSD.Color "LimeGreen"
            , XOSD.Display (XOSD.String (show n))]
          (const $ return ())

and at some point in the past I had ^V bound to this `name` function:

        , ((modMask conf , xK_v), name)


I think one of these two options should be ok.

I'd love to see someone wrap this all up even more easily!

-- Don


On Sun, May 8, 2011 at 4:29 PM, Lara Michaels
<laramichaels1978 at yahoo.com> wrote:
> Hi Don and everyone,
>
> From the screenshot this looks like exactly what I am looking for! Many thanks for sending me the link.
>
> I am afraid that I might need some additional hand-holding, though. :( I successfully installed both the Ubuntu libxosd-dev package as well as your xosd Haskell library. Can you tell me what I should do next?
>
>> Add a hook to your config file to bind a key sequence to
>> the workspace display.
>
> It is not clear to me what this means.
>
> Sorry and thank you for any further help
> lara
>
> --- On Sun, 5/8/11, Don Stewart <dons00 at gmail.com> wrote:
>
>> From: Don Stewart <dons00 at gmail.com>
>> Subject: Re: [xmonad] is it possible to display workspace number on the corresponding screen?
>> To: "Lara Michaels" <laramichaels1978 at yahoo.com>
>> Cc: xmonad at haskell.org
>> Date: Sunday, May 8, 2011, 6:47 PM
>> Uses this library:
>>
>>     http://hackage.haskell.org/package/xosd
>>
>> Add a hook to your config file to bind a key sequence to
>> the workspace display.
>>
>> On Sun, May 8, 2011 at 11:46 AM, Don Stewart <dons00 at gmail.com>
>> wrote:
>> > I wrote a little tool to do this, based on xosd a few
>> years ago,
>> >
>> > http://www.haskell.org/pipermail/xmonad/2008-November/006702.html
>> >
>> > you might adapt that.
>> >
>> > -- Don
>> >
>> > On Sun, May 8, 2011 at 8:42 AM, Lara Michaels
>> > <laramichaels1978 at yahoo.com>
>> wrote:
>> >> Hi everyone,
>> >>
>> >> I just moved to a three-screen setup at work and
>> am suffering from a curious problem: I cannot remember which
>> workspace is being displayed on each of the screens! That
>> makes it pretty time-consuming to switch one screen from its
>> current workspace to a different one.
>> >>
>> >> With the earlier help of list members, I am using
>> showWMName:
>> >>
>> >> import XMonad.Layout.ShowWName
>> >>
>> >> myLayout = layoutHook gnomeConfig -- part of
>> displaying current workspace name using
>> Xmonad.Layout.ShowWName
>> >>
>> >> main = xmonad $ ewmh gnomeConfig {
>> >>        manageHook = manageHook gnomeConfig
>> <+> composeAll myManageHook,
>> >>        workspaces = myWorkspaces,
>> >>        modMask = mod4Mask, -- makes all xmonad
>> shortcuts be "Windows key + X" (thus not interfering with
>> any app's)
>> >>        borderWidth        = 3,
>> >>        normalBorderColor  = "#cccccc",
>> >>        focusedBorderColor = "#cd8b00",
>> >>        layoutHook = showWName myLayout
>> >>        }
>> >>        `additionalKeysP` myKeys
>> >>
>> >> This gets me a small useful indication of which
>> workspace I am moving to *when I switch from one to the
>> other*.
>> >>
>> >> Similarly, is it possible to permanently display
>> in a corner (e.g., in the bottom-left corner) of each screen
>> the number of the workspace that is being displayed on that
>> screen? Or perhaps have the option of showing this same
>> information in the center of each screen by pressing a hot
>> key?
>> >>
>> >> With multihead setups (where I think xmonad really
>> shines), it is quite confusing not know which workspace you
>> are looking at on each screen... I only wish I understood
>> Haskell so that I could implement something like this. If
>> this is a small hack that can be accomplished with three
>> lines of code, please tell me how to do it! :)
>> >>
>> >> all the best and my thanks for any help
>> >> ~lara
>> >>
>> >> _______________________________________________
>> >> xmonad mailing list
>> >> xmonad at haskell.org
>> >> http://www.haskell.org/mailman/listinfo/xmonad
>> >>
>> >
>>
>



More information about the xmonad mailing list