diff options
author | Spencer Janssen <sjanssen@cse.unl.edu> | 2008-01-19 10:12:15 +0100 |
---|---|---|
committer | Spencer Janssen <sjanssen@cse.unl.edu> | 2008-01-19 10:12:15 +0100 |
commit | c8e06176657afde2170bfd0800f56df6bf9d7981 (patch) | |
tree | be1ed30b751f6d589eb67eaf1840a379f691aa33 /tests | |
parent | 33f724f49a802d979d420ef8dc9bde8e063ceea9 (diff) | |
download | xmonad-c8e06176657afde2170bfd0800f56df6bf9d7981.tar.gz xmonad-c8e06176657afde2170bfd0800f56df6bf9d7981.tar.xz xmonad-c8e06176657afde2170bfd0800f56df6bf9d7981.zip |
Roll testing into the main executable, use Cabal to build the tests
darcs-hash:20080119091215-a5988-8f5f48e8c40a0f39abdf6ffe4d4dc938ab8c7ef1.gz
Diffstat (limited to 'tests')
-rw-r--r-- | tests/Main.hs | 8 | ||||
-rw-r--r-- | tests/Properties.hs | 6 |
2 files changed, 3 insertions, 11 deletions
diff --git a/tests/Main.hs b/tests/Main.hs deleted file mode 100644 index b08d55b..0000000 --- a/tests/Main.hs +++ /dev/null @@ -1,8 +0,0 @@ -module Main where - -import qualified Properties - --- This will run all of the QC files for xmonad core. Currently, that's just --- Properties. If any more get added, sequence the main actions together. -main = do - Properties.main diff --git a/tests/Properties.hs b/tests/Properties.hs index 4f69f76..e96b03f 100644 --- a/tests/Properties.hs +++ b/tests/Properties.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -fglasgow-exts #-} +{-# OPTIONS -fglasgow-exts -w #-} module Properties where import XMonad.StackSet hiding (filter) @@ -52,7 +52,6 @@ instance (Integral i, Integral s, Eq a, Arbitrary a, Arbitrary l, Arbitrary sd) | s <- ls ] return $ fromList (fromIntegral n, sds,fs,ls,lay) - coarbitrary = error "no coarbitrary for StackSet" -- | fromList. Build a new StackSet from a list of list of elements, @@ -652,7 +651,7 @@ noOverlaps xs = and [ verts a `notOverlap` verts b main :: IO () main = do - args <- getArgs + args <- fmap (drop 1) getArgs let n = if null args then 100 else read (head args) (results, passed) <- liftM unzip $ mapM (\(s,a) -> printf "%-25s: " s >> a n) tests printf "Passed %d tests!\n" (sum passed) @@ -941,6 +940,7 @@ instance Arbitrary EmptyStackSet where l <- arbitrary -- there cannot be more screens than workspaces: return . EmptyStackSet . new l ns $ take (min (length ns) (length sds)) sds + coarbitrary = error "coarbitrary EmptyStackSet" -- | Generates a value that satisfies a predicate. suchThat :: Gen a -> (a -> Bool) -> Gen a |