mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 04:01:51 -07:00
X.U.ExtensibleConf: New helper module for extensible config
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. This requires changes to xmonad core: https://github.com/xmonad/xmonad/pull/294 A couple examples of what this gives us: * [X.H.RescreenHook](https://github.com/xmonad/xmonad-contrib/pull/460) can be made safe to apply multiple times, making it composable and usable in other contrib modules like X.H.StatusBar * `withSB` from X.H.StatusBar can also be made safe to apply multiple times, and we can even provide an API [similar to what we had before](https://hackage.haskell.org/package/xmonad-contrib-0.16/docs/XMonad-Hooks-DynamicLog.html#v:statusBar) if we want (probably not, consistency with the new dynamic status bars of https://github.com/xmonad/xmonad-contrib/pull/463 is more important) * The [X.H.EwmhDesktops refactor](https://github.com/xmonad/xmonad-contrib/pull/399) can possibly be made without breaking the `ewmh`/`ewmhFullscreen` API. And we will finally be able to have composable EWMH hooks. Related: https://github.com/xmonad/xmonad/pull/294
This commit is contained in:
31
tests/ExtensibleConf.hs
Normal file
31
tests/ExtensibleConf.hs
Normal file
@@ -0,0 +1,31 @@
|
||||
{-# OPTIONS_GHC -Wall #-}
|
||||
module ExtensibleConf where
|
||||
|
||||
import Test.Hspec
|
||||
|
||||
import XMonad
|
||||
import qualified XMonad.Util.ExtensibleConf as XC
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
specify "lookup" $
|
||||
XC.lookup def `shouldBe` (Nothing :: Maybe ())
|
||||
specify "lookup . add" $
|
||||
XC.lookup (XC.add "a" def) `shouldBe` Just "a"
|
||||
specify "lookup . add . add" $
|
||||
XC.lookup (XC.add "b" (XC.add "a" def)) `shouldBe` Just "ab"
|
||||
specify "lookup @String . add @String . add @[Int]" $
|
||||
XC.lookup (XC.add "a" (XC.add [1 :: Int] def)) `shouldBe` Just "a"
|
||||
specify "lookup @[Int] . add @String . add @[Int]" $
|
||||
XC.lookup (XC.add "a" (XC.add [1 :: Int] def)) `shouldBe` Just [1 :: Int]
|
||||
specify "lookup @() . add @String . add @[Int]" $
|
||||
XC.lookup (XC.add "a" (XC.add [1 :: Int] def)) `shouldBe` (Nothing :: Maybe ())
|
||||
|
||||
specify "once" $
|
||||
borderWidth (XC.once "a" incBorderWidth def) `shouldBe` succ (borderWidth def)
|
||||
specify "once . once" $
|
||||
borderWidth (XC.once "b" incBorderWidth (XC.once "a" incBorderWidth def))
|
||||
`shouldBe` succ (borderWidth def)
|
||||
|
||||
incBorderWidth :: XConfig l -> XConfig l
|
||||
incBorderWidth c = c{ borderWidth = succ (borderWidth c) }
|
@@ -3,6 +3,7 @@ module Main where
|
||||
import Test.Hspec
|
||||
import Test.Hspec.QuickCheck
|
||||
|
||||
import qualified ExtensibleConf
|
||||
import qualified ManageDocks
|
||||
import qualified NoBorders
|
||||
import qualified RotateSome
|
||||
@@ -43,3 +44,4 @@ main = hspec $ do
|
||||
prop "prop_spliInSubListsAt" $ XPrompt.prop_spliInSubListsAt
|
||||
prop "prop_skipGetLastWord" $ XPrompt.prop_skipGetLastWord
|
||||
context "NoBorders" $ NoBorders.spec
|
||||
context "ExtensibleConf" $ ExtensibleConf.spec
|
||||
|
Reference in New Issue
Block a user