diff options
author | Adam Vogt <vogt.adam@gmail.com> | 2010-04-19 03:49:46 +0200 |
---|---|---|
committer | Adam Vogt <vogt.adam@gmail.com> | 2010-04-19 03:49:46 +0200 |
commit | 1f2f6239a5d942d2cd0f06aeec2d96ab05980600 (patch) | |
tree | 5b789a736dc3a938f4bdb598b8ed0bd591878d2c | |
parent | 21033ad1ff3948c39dab6fca2e003acb6f575cc2 (diff) | |
download | XMonadContrib-1f2f6239a5d942d2cd0f06aeec2d96ab05980600.tar.gz XMonadContrib-1f2f6239a5d942d2cd0f06aeec2d96ab05980600.tar.xz XMonadContrib-1f2f6239a5d942d2cd0f06aeec2d96ab05980600.zip |
Rearrange tests. See test/genMain.hs for instructions.
Ignore-this: 1745e6f1052e84e40153b5b1c0a6e15a
darcs-hash:20100419014946-1499c-4705ec3d27ad26df038a7d72e978e5a137d712b5.gz
-rw-r--r-- | tests/Selective.hs (renamed from tests/test_Selective.hs) | 2 | ||||
-rw-r--r-- | tests/SwapWorkspaces.hs (renamed from tests/test_SwapWorkspaces.hs) | 3 | ||||
-rw-r--r-- | tests/XPrompt.hs (renamed from tests/test_XPrompt.hs) | 7 | ||||
-rw-r--r-- | tests/genMain.hs | 52 |
4 files changed, 62 insertions, 2 deletions
diff --git a/tests/test_Selective.hs b/tests/Selective.hs index 186f904..db00563 100644 --- a/tests/test_Selective.hs +++ b/tests/Selective.hs @@ -1,4 +1,6 @@ +{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE ScopedTypeVariables, FlexibleInstances #-} +module Selective where -- Tests for limitSelect-related code in L.LimitWindows. -- To run these tests, export (select,update,Selection(..),updateAndSelect) from diff --git a/tests/test_SwapWorkspaces.hs b/tests/SwapWorkspaces.hs index 148ab97..1cd33a0 100644 --- a/tests/test_SwapWorkspaces.hs +++ b/tests/SwapWorkspaces.hs @@ -1,4 +1,5 @@ -{-# OPTIONS -fglasgow-exts #-} +{-# LANGUAGE ScopedTypeVariables #-} +module SwapWorkspaces where import Data.List(find,union) import Data.Maybe(fromJust) diff --git a/tests/test_XPrompt.hs b/tests/XPrompt.hs index a4c6236..9c8ca8c 100644 --- a/tests/test_XPrompt.hs +++ b/tests/XPrompt.hs @@ -1,9 +1,10 @@ -{-# OPTIONS -fglasgow-exts #-} +{-# LANGUAGE ScopedTypeVariables #-} ------------------------------------- -- -- Tests for XPrompt and ShellPrompt -- ------------------------------------- +module XPrompt where import Data.Char import Test.QuickCheck @@ -12,11 +13,14 @@ import Data.List import XMonad.Prompt import qualified XMonad.Prompt.Shell as S +import Properties +{- instance Arbitrary Char where arbitrary = choose ('\32', '\255') coarbitrary c = variant (ord c `rem` 4) +-} doubleCheck p = check (defaultConfig { configMaxTest = 1000}) p deepCheck p = check (defaultConfig { configMaxTest = 10000}) p @@ -40,6 +44,7 @@ prop_spliInSubListsAt (x :: Int) (str :: [Char]) = prop_skipGetLastWord (str :: [Char]) = skipLastWord str ++ getLastWord str == str || skipLastWord str == getLastWord str + -- newIndex and newCommand get only non empy lists elemGen :: Gen ([String],String) elemGen = do diff --git a/tests/genMain.hs b/tests/genMain.hs new file mode 100644 index 0000000..90d8224 --- /dev/null +++ b/tests/genMain.hs @@ -0,0 +1,52 @@ +{-# LANGUAGE ViewPatterns #-} +{- | generate another Main from all modules in the current directory, +extracting all functions with @prop_@. + +Usage (your QuickCheck-1 version may vary): + +> ln -s ../../xmonad/tests/Properties.hs . +> runghc genMain.hs > Main.hs +> ghc -DTESTING -i.. -i. -package QuickCheck-1.2.0.0 Main.hs -e main + +-} +module Main where + +import Control.Monad.List +import Data.Char +import Data.IORef +import Data.List +import qualified Data.Set as S +import System.Directory +import System.FilePath +import Text.PrettyPrint.HughesPJ + +main = do + imports <- newIORef S.empty + props <- runListT $ do + f @ ((isUpper -> True) : (takeExtension -> ".hs")) + <- ListT (getDirectoryContents ".") + guard $ f `notElem` ["Main.hs", "Common.hs", "Properties.hs"] + let b = takeBaseName f + nesting <- io $ newIORef 0 + decl : _ <- ListT $ (map words . lines) `fmap` readFile f + case decl of + "{-" -> io $ modifyIORef nesting succ + "-}" -> io $ modifyIORef nesting pred + _ -> return () + 0 <- io $ readIORef nesting + guard $ "prop_" `isPrefixOf` decl + io $ modifyIORef imports (S.insert b) + return (b ++ "." ++ decl) + imports <- S.toList `fmap` readIORef imports + print $ genModule imports props + +genModule :: [String] -> [String] -> Doc +genModule imports props = vcat [header,imports', main ] + where + header = text "module Main where" + imports' = text "import Test.QuickCheck" + $$ vcat [ text "import qualified" <+> text im | im <- imports ] + props' = vcat [ text "quickCheck" <+> text p | p <- props ] + main = hang (text "main = do") 4 props' + +io x = liftIO x |