mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
This appears to be more natural. The function will most often be fixed by the module using `XC.once` and the configuration will often be supplied by users of those modules, so it's better to partially apply the function first.
32 lines
1.2 KiB
Haskell
32 lines
1.2 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" $
|
|
borderWidth (XC.once incBorderWidth "a" def) `shouldBe` succ (borderWidth def)
|
|
specify "once . once" $
|
|
borderWidth (XC.once incBorderWidth "b" (XC.once incBorderWidth "a" def))
|
|
`shouldBe` succ (borderWidth def)
|
|
|
|
incBorderWidth :: XConfig l -> XConfig l
|
|
incBorderWidth c = c{ borderWidth = succ (borderWidth c) }
|