Skip to content

Commit

Permalink
X.U.EZConfig: Add simple unit tests
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
slotThe committed Dec 13, 2021
1 parent 8abeb81 commit 520c518
Show file tree
Hide file tree
Showing 4 changed files with 51 additions and 1 deletion.
7 changes: 6 additions & 1 deletion XMonad/Util/EZConfig.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
--------------------------------------------------------------------
-- |
-- Module : XMonad.Util.EZConfig
Expand Down Expand Up @@ -34,7 +35,11 @@ module XMonad.Util.EZConfig (

parseKey, -- used by XMonad.Util.Paste
parseKeyCombo,
parseKeySequence, readKeySequence
parseKeySequence, readKeySequence,
#ifdef TESTING
functionKeys, specialKeys, multimediaKeys,
parseModifier,
#endif
) where

import XMonad
Expand Down
39 changes: 39 additions & 0 deletions tests/EZConfig.hs
Original file line number Diff line number Diff line change
@@ -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 <> ">"
2 changes: 2 additions & 0 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import qualified XPrompt
import qualified CycleRecentWS
import qualified OrgMode
import qualified GridSelect
import qualified EZConfig

main :: IO ()
main = hspec $ do
Expand Down Expand Up @@ -51,3 +52,4 @@ main = hspec $ do
context "CycleRecentWS" CycleRecentWS.spec
context "OrgMode" OrgMode.spec
context "GridSelect" GridSelect.spec
context "EZConfig" EZConfig.spec
4 changes: 4 additions & 0 deletions xmonad-contrib.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -388,6 +388,7 @@ test-suite tests
type: exitcode-stdio-1.0
main-is: Main.hs
other-modules: CycleRecentWS
EZConfig
ExtensibleConf
GridSelect
Instances
Expand All @@ -404,6 +405,7 @@ test-suite tests
XMonad.Actions.GridSelect
XMonad.Actions.PhysicalScreens
XMonad.Actions.RotateSome
XMonad.Actions.Submap
XMonad.Actions.SwapWorkspaces
XMonad.Actions.TagWindows
XMonad.Actions.WindowBringer
Expand All @@ -422,11 +424,13 @@ test-suite tests
XMonad.Prompt.Shell
XMonad.Util.Dmenu
XMonad.Util.Dzen
XMonad.Util.EZConfig
XMonad.Util.ExtensibleConf
XMonad.Util.ExtensibleState
XMonad.Util.Font
XMonad.Util.Image
XMonad.Util.Invisible
XMonad.Util.NamedActions
XMonad.Util.NamedWindows
XMonad.Util.Parser
XMonad.Util.PureX
Expand Down

0 comments on commit 520c518

Please sign in to comment.