Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Simplify the design of the manage hook #435

Open
wants to merge 7 commits into
base: master
Choose a base branch
from
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Jump to
Jump to file
Failed to load files.
Diff view
Diff view
66 changes: 66 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,76 @@

### Breaking Changes

* MVDT:

* The type of `runX` has changed.

* `windows` no longer performs an immediate refresh, but requests one.
That request is handled by `handleRefresh`.

* Deprecated `modifyWindowSet`, `windowBracket`, `windowBracket_` and
`sendMessageWithNoRefresh`.

* 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

* MVDT:

* X actions can now be combined without performing spurious refreshes.

* 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
35 changes: 20 additions & 15 deletions src/XMonad/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module XMonad.Core (
ManageHook, Query(..), runQuery, Directories'(..), Directories, getDirectories,
) where

import XMonad.Internal.Core (Internal)
import XMonad.StackSet hiding (modify)

import Prelude
Expand All @@ -47,10 +48,9 @@ import qualified Control.Exception as E
import Control.Applicative ((<|>), empty)
import Control.Monad.Fail
import Control.Monad.Fix (fix)
import Control.Monad.State
import Control.Monad.RWS
import Control.Monad.Reader
import Control.Monad (filterM, guard, void, when)
import Data.Semigroup
import Data.Traversable (for)
import Data.Time.Clock (UTCTime)
import Data.Default.Class
Expand Down Expand Up @@ -107,6 +107,7 @@ data XConf = XConf
-- the event currently being processed
, currentEvent :: !(Maybe Event) -- ^ event currently being processed
, directories :: !Directories -- ^ directories to use
, internal :: !(Internal WindowSet) -- ^ a hiding place for internals
}

-- todo, better name
Expand Down Expand Up @@ -157,22 +158,25 @@ newtype ScreenDetail = SD { screenRect :: Rectangle }

------------------------------------------------------------------------

-- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO'
-- encapsulating the window manager configuration and state,
-- respectively.
-- | The X monad; 'RWST' transformer over 'IO' encapsulating the window manager
-- configuration, model--view deviation and state, respectively.
--
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'. With newtype deriving we get readers and state monads
-- instantiated on 'XConf' and 'XState' automatically.
-- Dynamic components may be retrieved with 'get' and 'listen', static
-- components with 'ask'. With newtype deriving we get readers, writers and
-- state monads instantiated on 'XConf', 'Any' and 'XState' automatically.
--
newtype X a = X (ReaderT XConf (StateT XState IO) a)
deriving (Functor, Applicative, Monad, MonadFail, MonadIO, MonadState XState, MonadReader XConf)
newtype X a = X (RWST XConf Any XState IO a)
deriving
( Functor, Applicative, Monad, MonadFail, MonadIO
, MonadReader XConf, MonadWriter Any, MonadState XState
, MonadRWS XConf Any XState
)
deriving (Semigroup, Monoid) via Ap X 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
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Further, due to doFs now composing forwards rather than backwards,
many user configs will break silently.

You could keep the old order by making it Dual (Ap Query a), but then it becomes even harder to learn.

Expand All @@ -184,19 +188,20 @@ instance Default a => Default (Query a) where
def = return def

-- | Run the 'X' monad, given a chunk of 'X' monad code, and an initial state
-- Return the result, and final state
runX :: XConf -> XState -> X a -> IO (a, XState)
runX c st (X a) = runStateT (runReaderT a c) st
-- Return the result, final state and model--view deviation.
runX :: XConf -> XState -> X a -> IO (a, XState, Any)
runX c st (X rwsa) = runRWST rwsa c st

-- | Run in the 'X' monad, and in case of exception, and catch it and log it
-- to stderr, and run the error case.
catchX :: X a -> X a -> X a
catchX job errcase = do
st <- get
c <- ask
(a, s') <- io $ runX c st job `E.catch` \e -> case fromException e of
(a, s', mvd) <- io $ runX c st job `E.catch` \e -> case fromException e of
Just (_ :: ExitCode) -> throw e
_ -> do hPrint stderr e; runX c st errcase
tell mvd
put s'
return a

Expand Down
32 changes: 32 additions & 0 deletions src/XMonad/Internal/Core.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
{-# LANGUAGE NamedFieldPuns #-}

module XMonad.Internal.Core
( Internal, unsafeMakeInternal
, readView, unsafeWriteView
) where

import Data.IORef (IORef, newIORef, readIORef, writeIORef)

-- | An opaque data type for holding state and configuration that isn't to be
-- laid bare to the world outside, nor even to the rest of the package if we
-- can help it.
newtype Internal model = Internal
{ view :: IORef model -- ^ An 'IORef' to which we log the state of the view.
}

-- | The ability to construct an 'Internal' allows one to play tricks with
-- 'local'.
unsafeMakeInternal :: model -> IO (Internal model)
unsafeMakeInternal model = do
viewRef <- newIORef model
pure Internal
{ view = viewRef
}

readView :: Internal model -> IO model
readView Internal{view} = readIORef view

-- | The 'view' ref can only be safely written to with a just-rendered model.
unsafeWriteView :: Internal model -> model -> IO ()
unsafeWriteView Internal{view} = writeIORef view

18 changes: 18 additions & 0 deletions src/XMonad/Internal/Operations.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@

module XMonad.Internal.Operations
( rendered, unsafeLogView
) where

import Control.Monad.Reader (asks)
import XMonad.Internal.Core (readView, unsafeWriteView)
import XMonad.Core (X, WindowSet, internal, io, withWindowSet)

-- | Examine the 'WindowSet' that's currently rendered.
rendered :: X WindowSet
rendered = asks internal >>= io . readView

-- | See 'unsafeWriteView'.
unsafeLogView :: X ()
unsafeLogView = do
i <- asks internal
withWindowSet (io . unsafeWriteView i)
31 changes: 19 additions & 12 deletions src/XMonad/Main.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE BlockArguments #-}

----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -33,6 +34,7 @@ import Data.Monoid (getAll)
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
import Graphics.X11.Xlib.Extras

import XMonad.Internal.Core (unsafeMakeInternal)
import XMonad.Core
import qualified XMonad.Config as Default
import XMonad.StackSet (new, floating, member)
Expand Down Expand Up @@ -191,7 +193,9 @@ launch initxmc drs = do
initialWinset = let padToLen n xs = take (max n (length xs)) $ xs ++ repeat ""
in new layout (padToLen (length xinesc) (workspaces xmc)) $ map SD xinesc

cf = XConf
int <- unsafeMakeInternal initialWinset

let cf = XConf
{ display = dpy
, config = xmc
, theRoot = rootw
Expand All @@ -203,6 +207,7 @@ launch initxmc drs = do
, mousePosition = Nothing
, currentEvent = Nothing
, directories = drs
, internal = int
}

st = XState
Expand Down Expand Up @@ -234,18 +239,20 @@ launch initxmc drs = do

ws <- io $ scan dpy rootw

-- bootstrap the windowset, Operations.windows will identify all
-- the windows in winset as new and set initial properties for
-- those windows. Remove all windows that are no longer top-level
-- children of the root, they may have disappeared since
-- restarting.
let winset = maybe initialWinset windowset serializedSt
windows . const . foldr W.delete winset $ W.allWindows winset \\ ws
handleRefresh do
-- bootstrap the windowset, Operations.windows will identify all
-- the windows in winset as new and set initial properties for
-- those windows. Remove all windows that are no longer top-level
-- children of the root, they may have disappeared since
-- restarting.
let winset = maybe initialWinset windowset serializedSt
windows . const . foldr W.delete winset
$ W.allWindows winset \\ ws

-- manage the as-yet-unmanaged windows
mapM_ manage (ws \\ W.allWindows winset)
-- manage the as-yet-unmanaged windows
mapM_ manage (ws \\ W.allWindows winset)

userCode $ startupHook initxmc
userCode $ startupHook initxmc

rrData <- io $ xrrQueryExtension dpy

Expand All @@ -270,7 +277,7 @@ launch initxmc drs = do
-- | Runs handleEventHook from the configuration and runs the default handler
-- function if it returned True.
handleWithHook :: Event -> X ()
handleWithHook e = do
handleWithHook e = handleRefresh do
evHook <- asks (handleEventHook . config)
whenX (userCodeDef True $ getAll `fmap` evHook e) (handle e)

Expand Down
15 changes: 11 additions & 4 deletions src/XMonad/ManageHook.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,10 +21,12 @@ 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 +108,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