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 /tests/XPrompt.hs | |
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
Diffstat (limited to 'tests/XPrompt.hs')
-rw-r--r-- | tests/XPrompt.hs | 81 |
1 files changed, 81 insertions, 0 deletions
diff --git a/tests/XPrompt.hs b/tests/XPrompt.hs new file mode 100644 index 0000000..9c8ca8c --- /dev/null +++ b/tests/XPrompt.hs @@ -0,0 +1,81 @@ +{-# LANGUAGE ScopedTypeVariables #-} +------------------------------------- +-- +-- Tests for XPrompt and ShellPrompt +-- +------------------------------------- +module XPrompt where + +import Data.Char +import Test.QuickCheck + +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 +deepestCheck p = check (defaultConfig { configMaxTest = 100000}) p + +-- brute force check for exceptions +prop_split (str :: [Char]) = + forAll (elements str) $ \e -> S.split e str == S.split e str + +-- check if the first element of the new list is indeed the first part +-- of the string. +prop_spliInSubListsAt (x :: Int) (str :: [Char]) = + x < length str ==> result == take x str + where result = case splitInSubListsAt x str of + [] -> [] + x -> head x + +-- skipLastWord is complementary to getLastWord, unless the only space +-- in the string is the final character, in which case skipLastWord +-- and getLastWord will produce the same result. +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 + a <- arbitrary :: Gen [[Char]] + let l = case filter (/= []) a of + [] -> ["a"] + x -> x + e <- elements l + return (l,e) + +{- newIndex and newCommand have since been renamed or are no longer used + +-- newIndex calculates the index of the next completion in the +-- completion list, so the index must be within the range of the +-- copletions list +prop_newIndex_range = + forAll elemGen $ \(l,c) -> newIndex c l >= 0 && newIndex c l < length l +-} + +-- this is actually the definition of newCommand... +-- just to check something. +{- +prop_newCommandIndex = + forAll elemGen $ \(l,c) -> (skipLastWord c ++ (l !! (newIndex c l))) == newCommand c l +-} + +main = do + putStrLn "Testing ShellPrompt.split" + deepCheck prop_split + putStrLn "Testing spliInSubListsAt" + deepCheck prop_spliInSubListsAt + putStrLn "Testing skip + get lastWord" + deepCheck prop_skipGetLastWord + |