[xmonad] How do you test ManageHook using QuickCheck?

Takafumi Arakaki aka.tkf at gmail.com
Sun Feb 5 05:46:50 CET 2012


Hi,

I asked the same question in StackOverflow [1] but since I haven't
gotten an answer, let me ask here once again.  I guess this mailing
list is more appropriate place to ask.

I want to test ManageHooks in my xmonad.hs and I've heard there is
nice testing library called QuickCheck, so I am trying it.  I worte
the following code but could not make it work because XConf and XState
doesn't have required field.  I am not a haskell programmer, so maybe
I am doing something wrong.  I guess filling everything in XConf and
XState means connecting to the X server which is rather heavy for a
quick test.  It would be better if I can write something like
`StackSet i l a s sd -> ManageHook -> Bool`.


import XMonad.Core
import XMonad.ManageHook (doIgnore)
import XMonad.Config (defaultConfig)
import qualified XMonad.StackSet as W

import Test.QuickCheck (Property, quickCheck)
import Test.QuickCheck.Monadic (assert, monadicIO, run)


prop_manage_hook :: XConf -> XState -> ManageHook -> Property
prop_manage_hook c st mh = monadicIO $ do
  (_, newst) <- run $ runX c st $ runQuery mh $ theRoot c
  assert $ length (W.currentTag $ windowset newst) > 0

main :: IO ()
main = do
  quickCheck $ prop_manage_hook xc st doIgnore
  where
    xc = XConf { config = defaultConfig }
    st = XState {}


I once experienced xmonad halted because of a zero-division error I
had in my ManageHooks.  That's why I want to test it before putting in
my xmonad.hs.


[1] http://stackoverflow.com/questions/8552627/how-do-you-test-managehook-using-quickcheck

Thanks,
Takafumi



More information about the xmonad mailing list