[xmonad] Issues adapting XMonad.Util.Scratchpad for Conkeror in
0.8.1
aditya siram
aditya.siram at gmail.com
Mon Feb 2 22:29:42 EST 2009
Hi all,
Scratchpad is an XMonad extension that brings up or spawns a terminal window
on Alt-F2 (as I have it configured) and hides it in a hidden workspace when
I am done.
The code looked pretty simple and I tried to adapt this script to do the
same thing with my Conkeror window. This script worked until I upgraded to
0.8.1. Now it doesn't detect an existing Conkeror window and keeps launching
a new instance.
Xprop output shows the class name of Conkeror is: "Navigator", "Conkeror".
Since hpaste.org seems to be down, here it is my hacked Scratchpad sans
imports and header comment ( if the author of Scratchpad is reading this,
yes the code below is pretty much cut-and-paste):
---------------------------------------------------------------------------
-- | Action to pop up the browser, for the user to bind to a custom key.
scratchBrowserSpawn :: X ()
scratchBrowserSpawn =
scratchpadAction $ spawn "conkeror"
scratchpadAction :: X () -> X ()
scratchpadAction action = withWindowSet $ \s -> do
filterCurrent <- filterM (runQuery scratchpadQuery)
( (maybe [] W.integrate
. W.stack
. W.workspace
. W.current) s)
case filterCurrent of
(x:_) -> do
if null (filter ( (== scratchpadWorkspaceTag) . W.tag) (W.workspaces
s))
then addHiddenWorkspace scratchpadWorkspaceTag
else return ()
windows (W.shiftWin scratchpadWorkspaceTag x)
[] -> do
filterAll <- filterM (runQuery scratchpadQuery) (W.allWindows s)
case filterAll of
(x:_) -> windows (W.shiftWin (W.currentTag s) x)
[] -> action -- run the provided action to spawn it.
-- factored out since it appears in several places
scratchpadWorkspaceTag :: String
scratchpadWorkspaceTag = "BR"
-- factored out since this is common to both the ManageHook and the action
scratchpadQuery :: Query Bool
scratchpadQuery = (className =? "Conkeror") <||> (className =? "Navigator")
-- | The ManageHook, with the default rectangle:
-- Half the screen wide, a quarter of the screen tall, centered.
scratchpadManageHookDefault :: ManageHook
scratchpadManageHookDefault = scratchpadManageHook scratchpadDefaultRect
-- | The ManageHook, with a user-specified StackSet.RationalRect,
-- eg.
--
-- > scratchpadManageHook (W.RationalRect 0.25 0.375 0.5 0.25)
scratchpadManageHook :: W.RationalRect -- ^ User-specified screen rectangle.
-> ManageHook
scratchpadManageHook rect = scratchpadQuery --> doRectFloat rect
-- | Transforms a workspace list containing the SP workspace into one that
-- doesn't contain it. Intended for use with logHooks.
scratchpadFilterOutWorkspace :: [WindowSpace] -> [WindowSpace]
scratchpadFilterOutWorkspace = filter (\(W.Workspace tag _ _) -> tag /=
scratchpadWorkspaceTag)
scratchpadDefaultRect :: W.RationalRect
scratchpadDefaultRect = W.RationalRect 0.25 0.375 0.5 0.25
-------------------------------------------------------------------------------------------------
Thanks ...
Deech
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/xmonad/attachments/20090202/d784265e/attachment.htm
More information about the xmonad
mailing list