xmonad / xmonad-contrib

Contributed modules for xmonad
https://xmonad.org
BSD 3-Clause "New" or "Revised" License
589 stars 274 forks source link

Add X.U.ActionQueue And X.H.BorderPerWindow #640

Closed subbyte closed 2 years ago

subbyte commented 3 years ago

Description

Here's a functionality that no existing extension covers: default border width is 4; a user wants firefox and chromium to have 0 border and feh to have border width 16. The border width is permanent and no need to change when switching between layouts. And the user wants to avoid any unnecessary visual effects, e.g., window jumping.

12 years ago, users first discussed this need here. Unfortunately, no working solution was provided. At the end of the discussion, Magicloud said "the toggleBorder part does not work".

Recently I developed the same need, and asked the question in stackoverflow Config No Border For Specific Windows in Xmonad. After a few days, I figured out why Magicloud said ManageHook does not work (detailed in my answer) and wrote this PR to help others solve the same problem.

I put why I think this is the best way to realize the functionality and why there is no existing extension that implements exactly this in the docstring of the source code---the $design and $options sections.

Checklist

subbyte commented 3 years ago

I like this, thanks! I wonder if we should combine it with VoidBoders, somehow. The ergonomics are slightly worse (having to specify a manageHook in addition to a layout modifier) but it might sitll be worth it.

Good suggestion! I had the same thought. However, after writing the code, I find they are two functionalities:

  1. VoidBorders specifies a layout but not a window to set all windows borderless.
  2. BorderPerWindow specifies a window but not a layout to define border width.

I was thinking to combine them from the beginning, but I haven't figured out a good way for users to tell the combined module what to do. The current last step for both are layoutmodifier. To achieve VoidBorders, the user understands any layout it modifies will have all window borderless. To achieve BorderPerWindow, the user understands not all window in a layout decorated by BorderPerWindow will have customized border width. We could use a parameter to the combined module to indicate all windows, but that is confusing since the user also specifies border for each window.

The two modules look similar because part of the implementation approach they share. One step back, the original goal of BorderPerWindow is to not bother any layout, but focus on which window has which border setting. The config will not change in different layouts. I involve a layout hook because this is the only post-managehook-procedure I know (sorry about my limited knowledge of XMonad). I need to run setWindowBorderWidth after manage hook since XMonad do setWindowBorderWidth with default border config after applying all manage hooks. This also goes to your second code comment. I tried to do setWindowBorderWidth inside the manage hook (so we even do not need the layout hook), which is the Attempt A in my stackoverflow question but it does not work according to my answer.

To summarize, we may not want users to think this is a layout hook (named as XMonad.Hooks.BorderPerWindow) since this is per window config that applies to all layouts. The border setting is permanent, so it makes little sense to use it per layout (typical layout hook) like

myLayoutHook = Tall 1 (3/100) (1/2) ||| setBorderPerWindow Full ||| ...

The layout hook in the implementation is just an approach, not goal, and the meaningful way of using it is to apply it to all layouts since the window border setting will not be different between layouts.

myLayoutHook = setBorderPerWindow
             $ Tall 1 (3/100) (1/2) ||| Full ||| Grid ||| ...
geekosaur commented 3 years ago

If all you're looking for is to apply it post-manageHook, you may be looking for logHook instead of the layout.

subbyte commented 3 years ago

If all you're looking for is to apply it post-manageHook, you may be looking for logHook instead of the layout.

Thanks for the suggestion! Looks like a good one to check. Will try in a few days.

liskin commented 3 years ago

If all you're looking for is to apply it post-manageHook, you may be looking for logHook instead of the layout.

Thanks for the suggestion! Looks like a good one to check. Will try in a few days.

I'm a bit afraid that if you want to avoid the borders being seen for a split-second, logHook might be too late.

But I like the idea nonetheless. A generic logHook that executes little tasks from a queue might be useful elsewhere too. We have a couple usecases that would benefit from an afterManageHook, for example, and this seems like an easy way to implement that.

geekosaur commented 3 years ago

Actually they'll be seen very briefly even if it's in the layout, at least if the window is already mapped (I've caught it a few times). What's really needed is a way to override the default post-manageHook behavior, possibly by doing it pre-manageHook instead.

subbyte commented 3 years ago

Thank you for your guidance, @slotThe ! I simplified the code in my second commit, and tested it well.

I would like to try logHook as well to see if the implementation has any lag. However, I haven't figured out how to obtain XMonad Message in a logHook if I keep the manageHook part of the module. I still want to use manageHook since it provides a good way to specify windows. Please advice how I can move forward @geekosaur .

Besides the two, the best implementation in my mind is to have a post-window-management-hook after the window function, since the existing manageHook executes before it. Not sure if there are other functionalities sharing the same need to add the hook in XMonad.

liskin commented 3 years ago

I would like to try logHook as well to see if the implementation has any lag. However, I haven't figured out how to obtain XMonad Message in a logHook if I keep the manageHook part of the module.

My idea for the logHook-based implementation was that you'd simply make an ExtensibleState datatype holding a queue (a list that you then reverse before processing) of X () actions and a logHook that executes these actions and drops them from the queue. The manageHook would simply push withDisplay $ \d -> io $ setWindowBorderWidth d w bw directly into that queue.

And if this causes flicker, you can implement the same as a LayoutModifier, which should then execute the actions before the window is mapped.

I'm quite surprised we don't have both of those already… :-)

geekosaur commented 3 years ago

More or less what @liskin said, yes.

subbyte commented 3 years ago

My idea for the logHook-based implementation was that you'd simply make an ExtensibleState datatype holding a queue (a list that you then reverse before processing) of X () actions and a logHook that executes these actions and drops them from the queue. The manageHook would simply push withDisplay $ \d -> io $ setWindowBorderWidth d w bw directly into that queue.

Thanks for the point! If we do not make the X () action generic, I think we can just pass the data WindowBorderSpec in the queue, which I think I know how to write.

If we want to implement the X () actions in the queue, which can be anything returning X () like withDisplay $ \d -> io $ setWindowBorderWidth d w bw, I am thinking we may need a Monad like:

data WindowBorderSpec
    = WindowBorderSpec Window Dimension deriving (Read, Show)

newtype WindowBorderAction a = WindowBorderAction (ReaderT WindowBorderSpec X a)
    deriving (Functor, Applicative, Monad, MonadReader WindowBorderSpec, MonadIO)

runWindowBorderAction (WindowBorderAction m) spec = runReaderT m spec

type WindowBorderActionQueue = [WindowBorderAction]

instance ExtensionClass WindowBorderActionQueue where
    initialValue = []

I am not sure how to encapsulate WindowBorderActionQueue in a manageHook using ExtensibleState.modify (I see Query is a different monad based on X). Maybe I over-complicate the problem.

slotThe commented 3 years ago

Mh, I don't think we need an extra monad for this (if I understood the idea correctly). For a "queue" of actions we could define

newtype ActionQueue = ActionQueue { getQueue :: [X ()] }

instance ExtensionClass ActionQueue where
    initialValue :: ActionQueue
    initialValue = ActionQueue []

-- XS is XMonad.Util.ExtensibleState
appendQueue :: X () -> X ()
appendQueue a = XS.modify @ActionQueue $ coerce (a :) -- or just ActionQueue . ... . getQueue

and be good. The defineWindowBorder function would then simply add some action to that queue

defineWindowBorder :: Dimension -> ManageHook
defineWindowBorder bw = do
    w <- ask
    liftX $ appendQueue (withDisplay $ \d -> io $ setWindowBorderWidth d w bw)
    idHook

and users would have to add a logHook along the lines of

queueLogHook :: X ()
queueLogHook = do
    sequenceA_ . reverse . getQueue <$> XS.get 
    XS.put (ActionQueue [])

to their own logHook.

TheMC47 commented 3 years ago

Just coming by to say that I like the logHook idea better than a layout, but this is still an awesome feature @subbyte :tada:

liskin commented 3 years ago

and users would have to add a logHook along the lines of

queueLogHook :: X ()
queueLogHook = do
    sequenceA_ . reverse . getQueue <$> XS.get 
    XS.put (ActionQueue [])

to their own logHook.

Note that this isn't safe in general, as performing those actions can raise exceptions and the actions aren't removed from the queue then. So if we wanted to have something like this in Hooks or Util, we'd need to pop the actions before executing them, one by one. So this probably means using Data.Sequence instead of a list, unfortunately.

Just coming by to say that I like the logHook idea better than a layout, but this is still an awesome feature

Yeah, it's conceptually simpler and also safer. A general queue of X () actions to be executed during the layout would be dangerous if anyone called windows in there. On the other hand, I don't see another way to avoid flicker. It's a silly tradeoff. :-/

(Note that there are many other places in xmonad where flicker could be avoided with a more complicated design, but it's just not worth it. Perhaps this is another one of those?)

subbyte commented 3 years ago

Thanks for the guidance, @slotThe @liskin ! Will have a try to test it this week.

subbyte commented 2 years ago

Thanks @slotThe for the code! I tried it and fixed an issue that the sequenceA_ with <$> did not work (just unfolding the line makes it work yet I am not sure why). Here's the version that works finally:

newtype ActionQueue = ActionQueue { getQueue :: [X ()] }

instance ExtensionClass ActionQueue where
    initialValue = ActionQueue []

defineWindowBorder :: Dimension -> ManageHook
defineWindowBorder bw = do
    w <- ask
    liftX . XS.modify . append . withDisplay $ \d -> io $ setWindowBorderWidth d w bw
    idHook
  where
    append :: X () -> ActionQueue -> ActionQueue
    append x = coerce (x :)

queueLogHook :: X ()
queueLogHook = do
    as <- XS.get
    sequenceA_ . reverse $ getQueue as
    XS.put (ActionQueue [])

Before improving the realization using Data.Sequence and pop-n-execute each action as @liskin suggested, I tested the latency and visual effect of the logHook approach.

xmonad-640-loghook-approach-issue

subbyte commented 2 years ago

Another thought, which is not related to the issue above but related to the improvement of realization @liskin mentioned: a window is created at a time, and there is a logHook function in the window creation handler. For this extension only, we may not need to support a queue of actions, just

newtype BorderAction = BorderAction { getAction :: X () }

Since each border adjustment action will be processed for each window creation.

A potential issue is when window creation is too fast, and the windows function hasn't finished for one window while another one is executed, so BorderAction may be overwritten or overcleared by each. Please comment if window creation events are handled in a multi-threading model with shared ExtensibleState and this is the reason for the queue.

liskin commented 2 years ago
  • However, there is an issue: a new window created without border will not be re-rendered after the border is removed, which leaves blank (background) of double border width at the right and bottom of the window (see screenshot below for example). Next if I switch to another workspace and switch back, then the window is re-rendered and there is no blank space any more. Actually I experience the same when using XMonad.Actions.NoBorders. Not sure if this is my configuration issue or a logic issue without involving the XMonad layout procedure.

I'm afraid this is a logic issue. When the border width is changed, the window effectively becomes smaller, and it's only resized to the correct size on the next refresh: https://github.com/xmonad/xmonad/blob/54df2e9acdbdd85b830865464bd89b36688b9963/src/XMonad/Operations.hs#L192 https://github.com/xmonad/xmonad/blob/54df2e9acdbdd85b830865464bd89b36688b9963/src/XMonad/Operations.hs#L310

So to make this work in a logHook, you might need to get the current border width using withWindowAttributes and moveResizeWindow to compensate for the border width change. Or just refresh, which might result in some flicker.

For this extension only, we may not need to support a queue of actions, just…

The point of having a queue is that a) it's useful for other modules as well and perhaps even useful for user configs in general, b) it's conceptually simpler—you don't need to think hard whether you need to store one, zero-or-one, zero-or-more or one-or-more.

subbyte commented 2 years ago

So to make this work in a logHook, you might need to get the current border width using withWindowAttributes and moveResizeWindow to compensate for the border width change. Or just refresh, which might result in some flicker.

Now it is important to pop an action before executing it if I use refresh, which basically calls windows, at the end of which the logHook is invoked again.

To put action queue as a generic function others can use as well, we may want to create two modules: one for action queue, and one for the border customization. Here's the code I tested to work:

-- XMonad/Utils/ActionQueue.hs
-- exporting `executeActionQueue` and `appendActionQueue`
newtype ActionQueue = ActionQueue { getQueue :: Seq (X ()) }

instance ExtensionClass ActionQueue where
    initialValue = ActionQueue empty

appendActionQueue :: X () -> ActionQueue -> ActionQueue
appendActionQueue a (ActionQueue as) = ActionQueue (as |> a)

executeActionQueue :: X ()
executeActionQueue = XS.get >>= executeActionSeq <$> getQueue

executeActionSeq :: Seq (X ()) -> X ()
executeActionSeq Empty = XS.put $ ActionQueue empty
executeActionSeq (a :<| as) = (XS.put $ ActionQueue as) >> a
-- XMonad/Hooks/BorderPerWindow.hs
-- exporting `defineWindowBorder`
defineWindowBorder :: Dimension -> ManageHook
defineWindowBorder bw = do
    w <- ask
    liftX . XS.modify . appendActionQueue $ (setBorder w bw >> refresh)
    idHook

setBorder :: Window -> Dimension -> X ()
setBorder w bw = withDisplay $ \d -> io $ setWindowBorderWidth d w bw

This code does not yield much flicker effect (sometimes a little bit) and I feel good with the testing results. If I do

    liftX . XS.modify . appendActionQueue $ setBorder w bw
    liftX . XS.modify . appendActionQueue $ refresh

instead of putting it in one action, I see obvious flicker every time.

Please advice if this is the way the community would like, especially whether splitting it into two modules is a good idea. Then I will rebase the PR to the logHook approach for further code review.

slotThe commented 2 years ago

On Mon, Nov 15 2021 21:17, Xiaokui Shu wrote:

liftX . XS.modify . appendActionQueue $ (setBorder w bw >> refresh)

I wonder if we could put refresh as the Empty case of executeActionQueue or if that would be too late (it would certainly save us many calls to it)

Please advice if this is the way the community would like, especially whether splitting it into two modules is a good idea. Then I will rebase the PR to the logHook approach for further code review.

Oh yeah, I think the original idea definitely was to have an action queue as a separate module and let this module just use it via importing it

subbyte commented 2 years ago

I wonder if we could put refresh as the Empty case of executeActionQueue or if that would be too late (it would certainly save us many calls to it)

I tried two ways to remove refresh into Seq pattern matching in executeActionSeq:

  1. executeActionSeq Empty = refresh: this will trigger a logic bomb that XMonad uses 100% CPU on a single core and restarting XMonad cannot release since refresh has logHook (in windows), which will do refresh recursively on empty ActionQueue.

  2. I think I should do:

    executeActionSeq :: Seq (X ()) -> X ()
    executeActionSeq Empty = pure ()
    executeActionSeq (a :<| Empty) = (XS.put $ ActionQueue empty) >> a >> refresh
    executeActionSeq (a :<| as) = (XS.put $ ActionQueue as) >> a

    This works. In theory and in practice, I don't find this differs from my previous version: for the window border use case, only one window is opened at a time, and the queue is at most one action before it is cleared in windows function (logHook at the end). In my old code, the single action is actually two: border setup and refresh. In the new code, the single action is just border setup, plus the refresh when this single (last) action is cleared.

I think we may need to think from the generic ActionQueue module perspective whether we need refresh for actions (of any use cases) to be cleared. This may be not necessary or not the intention of the developer who is using ActionQueue.

liskin commented 2 years ago
-- XMonad/Utils/ActionQueue.hs
-- exporting `executeActionQueue` and `appendActionQueue`
newtype ActionQueue = ActionQueue { getQueue :: Seq (X ()) }

instance ExtensionClass ActionQueue where
    initialValue = ActionQueue empty

appendActionQueue :: X () -> ActionQueue -> ActionQueue
appendActionQueue a (ActionQueue as) = ActionQueue (as |> a)

executeActionQueue :: X ()
executeActionQueue = XS.get >>= executeActionSeq <$> getQueue

executeActionSeq :: Seq (X ()) -> X ()
executeActionSeq Empty = XS.put $ ActionQueue empty
executeActionSeq (a :<| as) = (XS.put $ ActionQueue as) >> a

This looks like executeActionSeq only executes the head of the queue, and leaves the rest for the next logHook invocation. Does that explain the flicker? (Actually I'd expect much more than that, a noticeable delay.)

liskin commented 2 years ago

And I don't think the queue itself should be forcing the refresh. It's a logic bomb, and trying to hack it into not being a logic bomb is futile.

subbyte commented 2 years ago

This looks like executeActionSeq only executes the head of the queue, and leaves the rest for the next logHook invocation. Does that explain the flicker? (Actually I'd expect much more than that, a noticeable delay.)

Good catch! There is a logic error here.

However, I avoid the logic error by luck since the queue is at most one action long before it is cleared in windows function for the window border use case as I explained earlier. For generic ActionQueue uses, I should execute all actions. Let me update.

subbyte commented 2 years ago

Basic code submitted. Feel free to comment. I will add docs in the next days.

One strange thing: this logHook approach works without visible flicker for most windows such as chromium and gvim. However, firefox gives me a strange behavior: the window is first drawn with border, then the border is removed and the window is moved to the bottom left to the screen. This is different from the phenomenon I encountered without refresh, where

  1. the window is moved to the top left (this time bottom left)
  2. the desktop background is visible for the non-border area (this time just black)
  3. all windows have the issue (this time only firefox)
  4. switch to another workspace and back will rerender it correctly (this time not, the black part is always there until I open another window on the same workspace)

See attached screenshot for example. Any idea why?

2021-11-17-003211_2560x1440_scrot

subbyte commented 2 years ago

Never mind the firefox issue. This traces back to a bug with firefox and nvidia driver. I configured firefox with layers.offmainthreadcomposition.force-disabled:true according to this post, and it works now.

No flicker for any window with the logHook approach now.

subbyte commented 2 years ago

Thanks guys @slotThe @liskin ! I pushed a new commit including the doc and a little code editing to make them more modular. Going forward, may I ask what I need to do to make it a branch here for you to upgrade?

slotThe commented 2 years ago

I will merge this for now, since the largest issues (using ExtensibleConf and executing the actions one by one) are fixed now. If we still see anything that needs to be improved we can always push another commit afterwards

Thanks!

ixzh commented 2 years ago

the doc example seems to have a typo:

myManageHook = composeAll
    [ className =? "firefox"  --> defineWindowWidth 0
    , className =? "Chromium" --> defineWindowWidth 0
    , isDialog                --> defineWindowWidth 8
    ]

defineWindowWidth to be defineBorderWidth?

slotThe commented 2 years ago

Oh indeed, thanks! Fixed by 853264b1134b17ff35dd3175f01ce1770c6c424d