xmonad-contrib/tests/ExtensibleConf.hs
Tomas Janousek 3a72dd5355 X.U.ExtensibleConf: Add high-level idioms for non-Semigroup, but Default types
For configuration values that don't compose well using a Semigroup
instance, provide a high-level API allowing arbitrary modification of
the value, taking its Default if absent. This API is only usable for
separate configuration data and cannot be used to guard addition of hook
using `once`.
2021-10-20 14:46:52 +01:00

42 lines
1.5 KiB
Haskell

{-# 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" $ do
let c = XC.once incBorderWidth "a" def
borderWidth c `shouldBe` succ (borderWidth def)
XC.lookup c `shouldBe` Just "a"
specify "once . once" $ do
let c = XC.once incBorderWidth "b" (XC.once incBorderWidth "a" def)
borderWidth c `shouldBe` succ (borderWidth def)
XC.lookup c `shouldBe` Just "ab"
specify "modifyDef" $ do
let c = XC.modifyDef (<> "a") def
XC.lookup c `shouldBe` Just "a"
specify "modifyDef . modifyDef" $ do
let c = XC.modifyDef (<> "b") (XC.modifyDef (<> "a") def)
XC.lookup c `shouldBe` Just "ab"
incBorderWidth :: XConfig l -> XConfig l
incBorderWidth c = c{ borderWidth = succ (borderWidth c) }