Skip to content

Commit

Permalink
MVDT: Simplify the design of the manage hook
Browse files Browse the repository at this point in the history
`ManageHook` as `Query (Endo WindowSet)` is a holdover from The Old Way.

`Query` wraps the `X` Monad, which already collects and composes changes
to the windowset. As such, the `Endo WindowSet` is redundant. Worse, the
way these changes compose is not at all obvious or intuitive.

Suppose you compose two ManageHook values:

    manageHook = (qF $> Endo f)
              <> (qG $> Endo g)

The result of running the `manageHook` on some `w` is not, as one might
guess,

    do
      runQuery qF w
      windows f
      runQuery qG w
      windows g

nor is it

    do
      runQuery qF w
      runQuery qG w
      windows f
      windows g

Unfortunately, it is:

    do
      runQuery qF w
      runQuery qG w
      windows g
      windows f

This is a wart, and it's one we can now excise.

Hence the `ManageHook` type synonym is simplified to `Query ()`, and
`manage` runs the hook as-is. It also performs the initial handling of
the window beforehand, so it's fully visible within the hook. As such,
`willFloat` (which repeats the indirect logic in `manage`) is deprecated
in favour of `isFloat`, which directly references the model.

Note that this change also allows cleaner syntax in configuration. E.g.

    manageHook = composeAll
      [ test1 --> fooHook
      , test2 --> barQueryAction >> idHook
      , test3 --> fooHook <> bazHook <> quuxHook
      ]

can become

    manageHook = do
      test1 --> fooHook
      test2 --> barQueryAction
      test3 --> do
        fooHook
        bazHook
        quuxHook

To accomodate the change, `doF` must become a lifted `windows`, but that
and monoid-polymorphism take care of adjusting the rest of the core
interface transparently.

As such, simple configs will continue to compile, but extensions that
directly interfered with the old `Endo WindowSet` won't.

Further, due to `doF`s now composing forwards rather than backwards,
many user configs will break silently. The solution is to reverse the
order that `doF`, `doFloat`, `doIgnore` and `doShift` appear in,
extending that list to include anything else built on `doF`, like
`doShiftTo` or `doFullFloat` from `X.H.ManageHelpers`.
  • Loading branch information
LSLeary committed Dec 19, 2022
1 parent 506b13c commit 52f508c
Show file tree
Hide file tree
Showing 4 changed files with 62 additions and 7 deletions.
47 changes: 47 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,29 @@

* Extended `XConf` with a new `internal` field.

* The definition of the `ManageHook` type synonym has changed.

* The order of manage hook composition has been reversed, though the order
in which matching and `liftX` actions are performed has not.

As such, e.g.

```haskell
manageHook = composeAll
[ test1 --> doSomething <> liftX someAction >> idHook
, test2 --> doThird <> doSecond <> doFirst
]
```

should be corrected to

```haskell
manageHook = composeAll
[ test1 --> doSomething <> liftX someAction >> idHook
, test2 --> doFirst <> doSecond <> doThird
]
```

* Dropped support for GHC 8.4.

### Enhancements
Expand All @@ -27,6 +50,30 @@
* New operations: `norefresh`, `handleRefresh`, `respace`,
`messageWorkspace` and `rendered`.

* `ManageHook` supports new syntax.

Instead of, e.g.

```haskell
manageHook = composeAll
[ test1 --> fooHook
, test2 --> barQueryAction >> idHook
, test3 --> fooHook <> bazHook <> quuxHook
]
```

you can now write

```haskell
manageHook = do
test1 --> fooHook
test2 --> barQueryAction
test3 --> do
fooHook
bazHook
quuxHook
```

* Exported `sendRestart` and `sendReplace` from `XMonad.Operations`.

* Exported `buildLaunch` from `XMonad.Main`.
Expand Down
2 changes: 1 addition & 1 deletion src/XMonad/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -176,7 +176,7 @@ newtype X a = X (RWST XConf Any XState IO a)
instance Default a => Default (X a) where
def = return def

type ManageHook = Query (Endo WindowSet)
type ManageHook = Query ()
newtype Query a = Query (ReaderT Window X a)
deriving (Functor, Applicative, Monad, MonadReader Window, MonadIO)
deriving (Semigroup, Monoid) via Ap Query a
Expand Down
14 changes: 11 additions & 3 deletions src/XMonad/ManageHook.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,10 +21,13 @@ import Graphics.X11.Xlib (Display, Window, internAtom, wM_NAME)
import Control.Exception (bracket, SomeException(..))
import qualified Control.Exception as E
import Control.Monad.Reader
import Control.Monad.State
import Data.Maybe
import Data.Monoid
import qualified Data.Map as M
import qualified XMonad.StackSet as W
import XMonad.Operations (floatLocation, reveal, isFixedSizeOrTransient)
import XMonad.Operations
(floatLocation, reveal, isFixedSizeOrTransient, windows)

-- | Lift an 'X' action to a 'Query'.
liftX :: X a -> Query a
Expand Down Expand Up @@ -106,12 +109,17 @@ getStringProperty d w p = do
return $ fmap (map (toEnum . fromIntegral)) md

-- | Return whether the window will be a floating window or not
{-# DEPRECATED willFloat "Use isFloat." #-}
willFloat :: Query Bool
willFloat = ask >>= \w -> liftX $ withDisplay $ \d -> isFixedSizeOrTransient d w

-- | Return whether the window is a floating window or not
isFloat :: Query Bool
isFloat = ask >>= \w -> liftX $ gets (M.member w . W.floating . windowset)

-- | Modify the 'WindowSet' with a pure function.
doF :: (s -> s) -> Query (Endo s)
doF = return . Endo
doF :: (WindowSet -> WindowSet) -> ManageHook
doF = liftX . windows

-- | Move the window to the floating layer.
doFloat :: ManageHook
Expand Down
6 changes: 3 additions & 3 deletions src/XMonad/Operations.hs
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ import qualified XMonad.StackSet as W
import XMonad.Internal.Operations (rendered, unsafeLogView)

import Data.Maybe
import Data.Monoid (Endo(..),Any(..))
import Data.Monoid (Any(..))
import Data.List (nub, (\\), find)
import Data.Bits ((.|.), (.&.), complement, setBit, testBit)
import Data.Function (on)
Expand Down Expand Up @@ -123,10 +123,10 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do

f | shouldFloat = W.float w (adjust rr)
| otherwise = id
windows (f . W.insertUp w)

mh <- asks (manageHook . config)
g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
windows (g . f . W.insertUp w)
userCodeDef () (runQuery mh w)

-- | A window no longer exists; remove it from the window
-- list, on whatever workspace it is.
Expand Down

0 comments on commit 52f508c

Please sign in to comment.