]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Misc.hs
Define a few tests locally.
[spline3.git] / src / Misc.hs
index 090642a223d6e2f2493441445dcd1dfba8e5e969..b1cb1affcce0a53463c5f9ae400c5da27fabd157 100644 (file)
@@ -3,6 +3,13 @@
 module Misc
 where
 
+import qualified Data.Vector as V (Vector, elem, empty, filter)
+import Test.Framework (Test, testGroup)
+import Test.Framework.Providers.HUnit (testCase)
+import Test.Framework.Providers.QuickCheck2 (testProperty)
+import Test.HUnit (Assertion, assertEqual)
+import Test.QuickCheck
+
 
 -- | The standard factorial function. See
 --   <http://www.willamette.edu/~fruehr/haskell/evolution.html> for
@@ -47,7 +54,7 @@ transpose_xz m =
     where
       zsize = (length m) - 1
       ysize = length (head m) - 1
-      xsize = (length $ head $ head m) - 1
+      xsize = length (head $ head m) - 1
 
 -- | Takes a list, and returns True if its elements are pairwise
 --   equal. Returns False otherwise.
@@ -57,3 +64,51 @@ all_equal xs =
     where
       first_element  = head xs
       other_elements = tail xs
+
+
+-- | Returns 'True' if the vectors xs and ys are disjoint, 'False'
+--   otherwise.
+--
+--   Examples:
+--
+--   >>> let xs = Data.Vector.fromList [1,2,3]
+--   >>> let ys = Data.Vector.fromList [4,5,6]
+--   >>> disjoint xs ys
+--   True
+--
+--   >>> let ys = Data.Vector.fromList [3,4,5]
+--   >>> disjoint xs ys
+--   False
+--
+disjoint :: (Eq a) => V.Vector a -> V.Vector a -> Bool
+disjoint xs ys =
+  intersect xs ys == V.empty
+  where
+    intersect :: (Eq a) => V.Vector a -> V.Vector a -> V.Vector a
+    intersect ws zs =
+      V.filter (`V.elem` zs) ws
+
+prop_factorial_greater :: Int -> Property
+prop_factorial_greater n =
+    n <= 20 ==> factorial n >= n
+
+
+test_flatten1 :: Assertion
+test_flatten1 =
+    assertEqual "flatten actually works" expected_list actual_list
+    where
+      target = [[[1::Int]], [[2, 3]]]
+      expected_list = [1, 2, 3]
+      actual_list = flatten target
+
+
+misc_tests :: Test.Framework.Test
+misc_tests =
+    testGroup "Misc Tests" [
+      testCase "flatten (1)" test_flatten1 ]
+
+
+misc_properties :: Test.Framework.Test
+misc_properties =
+    testGroup "Misc Properties" [
+      testProperty "factorial greater" prop_factorial_greater ]