X.U.EZConfig: Add simple unit tests

Add very basic unit tests for EZConfig to see if it can parse all of the
keys (and key combinations) that it promises to parse.

The long-term goal here should be to write a pretty-printer for EZConfig
and to check whether that's a proper inverse (either in the normal sense
or in the inverse semigroup sense), as the tests for X.P.OrgMode do.
This commit is contained in:
slotThe 2021-11-29 17:48:03 +01:00
parent 8abeb81fd0
commit 520c51817a
4 changed files with 51 additions and 1 deletions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-------------------------------------------------------------------- --------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Util.EZConfig -- Module : XMonad.Util.EZConfig
@ -34,7 +35,11 @@ module XMonad.Util.EZConfig (
parseKey, -- used by XMonad.Util.Paste parseKey, -- used by XMonad.Util.Paste
parseKeyCombo, parseKeyCombo,
parseKeySequence, readKeySequence parseKeySequence, readKeySequence,
#ifdef TESTING
functionKeys, specialKeys, multimediaKeys,
parseModifier,
#endif
) where ) where
import XMonad import XMonad

39
tests/EZConfig.hs Normal file
View File

@ -0,0 +1,39 @@
module EZConfig (spec) where
import Control.Arrow (first)
import Test.Hspec
import XMonad
import XMonad.Prelude
import XMonad.Util.EZConfig
import XMonad.Util.Parser
spec :: Spec
spec = do
context "parseKey" $ do
let prepare = unzip . map (first surround)
testParseKey (ns, ks) = traverse (runParser parseKey) ns `shouldBe` Just ks
it "parses all regular keys" $ testParseKey regularKeys
it "parses all function keys" $ testParseKey (prepare functionKeys )
it "parses all special keys" $ testParseKey (prepare specialKeys )
it "parses all multimedia keys" $ testParseKey (prepare multimediaKeys)
context "parseModifier" $ do
it "parses all combinations of modifiers" $
nub . map sort <$> traverse (runParser (many $ parseModifier def))
modifiers
`shouldBe` Just [[ shiftMask, controlMask
, mod1Mask, mod1Mask -- def M and M1
, mod2Mask, mod3Mask, mod4Mask, mod5Mask
]]
regularKeys :: ([String], [KeySym])
regularKeys = unzip . map (first (: ""))
$ zip ['!' .. '~' ] [xK_exclam .. xK_asciitilde]
++ zip ['\xa0' .. '\xff'] [xK_nobreakspace .. xK_ydiaeresis]
-- | QuickCheck can handle the 8! combinations just fine.
modifiers :: [String]
modifiers = map concat $
permutations ["M-", "C-", "S-", "M1-", "M2-", "M3-", "M4-", "M5-"]
surround :: String -> String
surround s = "<" <> s <> ">"

View File

@ -13,6 +13,7 @@ import qualified XPrompt
import qualified CycleRecentWS import qualified CycleRecentWS
import qualified OrgMode import qualified OrgMode
import qualified GridSelect import qualified GridSelect
import qualified EZConfig
main :: IO () main :: IO ()
main = hspec $ do main = hspec $ do
@ -51,3 +52,4 @@ main = hspec $ do
context "CycleRecentWS" CycleRecentWS.spec context "CycleRecentWS" CycleRecentWS.spec
context "OrgMode" OrgMode.spec context "OrgMode" OrgMode.spec
context "GridSelect" GridSelect.spec context "GridSelect" GridSelect.spec
context "EZConfig" EZConfig.spec

View File

@ -388,6 +388,7 @@ test-suite tests
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
main-is: Main.hs main-is: Main.hs
other-modules: CycleRecentWS other-modules: CycleRecentWS
EZConfig
ExtensibleConf ExtensibleConf
GridSelect GridSelect
Instances Instances
@ -404,6 +405,7 @@ test-suite tests
XMonad.Actions.GridSelect XMonad.Actions.GridSelect
XMonad.Actions.PhysicalScreens XMonad.Actions.PhysicalScreens
XMonad.Actions.RotateSome XMonad.Actions.RotateSome
XMonad.Actions.Submap
XMonad.Actions.SwapWorkspaces XMonad.Actions.SwapWorkspaces
XMonad.Actions.TagWindows XMonad.Actions.TagWindows
XMonad.Actions.WindowBringer XMonad.Actions.WindowBringer
@ -422,11 +424,13 @@ test-suite tests
XMonad.Prompt.Shell XMonad.Prompt.Shell
XMonad.Util.Dmenu XMonad.Util.Dmenu
XMonad.Util.Dzen XMonad.Util.Dzen
XMonad.Util.EZConfig
XMonad.Util.ExtensibleConf XMonad.Util.ExtensibleConf
XMonad.Util.ExtensibleState XMonad.Util.ExtensibleState
XMonad.Util.Font XMonad.Util.Font
XMonad.Util.Image XMonad.Util.Image
XMonad.Util.Invisible XMonad.Util.Invisible
XMonad.Util.NamedActions
XMonad.Util.NamedWindows XMonad.Util.NamedWindows
XMonad.Util.Parser XMonad.Util.Parser
XMonad.Util.PureX XMonad.Util.PureX