mirror of
https://github.com/xmonad/xmonad.git
synced 2025-07-25 17:21:52 -07:00
Add support for extensible config in contrib modules
It's often difficult to make contrib modules work together. When one depends on a functionality of another, it is often necessary to expose lots of low-level functions and hooks and have the user combine these into a complex configuration that works. This is error-prone, and arguably a bad UX in general. This commit presents a simple solution to that problem inspired by "extensible state": extensible config. It allows contrib modules to store custom configuration values inside XConfig. This lets them create custom hooks, ensure they hook into xmonad core only once, and possibly other use cases I haven't thought of yet. For more, see the related pull request to xmonad-contrib. Related: https://github.com/xmonad/xmonad-contrib/pull/547
This commit is contained in:
@@ -41,6 +41,9 @@
|
||||
Instead, the manpage source is regenerated and manpage rebuilt
|
||||
automatically in CI.
|
||||
|
||||
* Added the `extensibleConf` field to `XConfig` which makes it easier for
|
||||
contrib modules to have composable configuration (custom hooks, …).
|
||||
|
||||
## 0.15 (September 30, 2018)
|
||||
|
||||
* Reimplement `sendMessage` to deal properly with windowset changes made
|
||||
|
@@ -277,6 +277,7 @@ instance (a ~ Choose Tall (Choose (Mirror Tall) Full)) => Default (XConfig a) wh
|
||||
, XMonad.handleExtraArgs = \ xs theConf -> case xs of
|
||||
[] -> return theConf
|
||||
_ -> fail ("unrecognized flags:" ++ show xs)
|
||||
, XMonad.extensibleConf = M.empty
|
||||
}
|
||||
|
||||
-- | The default set of configuration values itself
|
||||
|
@@ -23,7 +23,7 @@ module XMonad.Core (
|
||||
XConf(..), XConfig(..), LayoutClass(..),
|
||||
Layout(..), readsLayout, Typeable, Message,
|
||||
SomeMessage(..), fromMessage, LayoutMessages(..),
|
||||
StateExtension(..), ExtensionClass(..),
|
||||
StateExtension(..), ExtensionClass(..), ConfExtension(..),
|
||||
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
|
||||
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
|
||||
getAtom, spawn, spawnPID, xfork, recompile, trace, whenJust, whenX,
|
||||
@@ -122,6 +122,11 @@ data XConfig l = XConfig
|
||||
, rootMask :: !EventMask -- ^ The root events that xmonad is interested in
|
||||
, handleExtraArgs :: !([String] -> XConfig Layout -> IO (XConfig Layout))
|
||||
-- ^ Modify the configuration, complain about extra arguments etc. with arguments that are not handled by default
|
||||
, extensibleConf :: !(M.Map TypeRep ConfExtension)
|
||||
-- ^ Stores custom config information.
|
||||
--
|
||||
-- The module "XMonad.Util.ExtensibleConf" in xmonad-contrib
|
||||
-- provides additional information and a simple interface for using this.
|
||||
}
|
||||
|
||||
|
||||
@@ -383,7 +388,7 @@ data LayoutMessages = Hide -- ^ sent when a layout becomes non-visi
|
||||
instance Message LayoutMessages
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- Extensible state
|
||||
-- Extensible state/config
|
||||
--
|
||||
|
||||
-- | Every module must make the data it wants to store
|
||||
@@ -410,6 +415,9 @@ data StateExtension =
|
||||
| forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a
|
||||
-- ^ Persistent extension
|
||||
|
||||
-- | Existential type to store a config extension.
|
||||
data ConfExtension = forall a. Typeable a => ConfExtension a
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- | General utilities
|
||||
--
|
||||
|
Reference in New Issue
Block a user