]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Misc.hs
src/Misc.hs: add a type signature to eliminate polymorphism.
[spline3.git] / src / Misc.hs
index b9322ef0c2d49b23f26350af2e32eb04b403b2d5..56d33eb43c3969ce0c9c40b5efb81582d0b888b1 100644 (file)
@@ -1,15 +1,22 @@
 {-# LANGUAGE BangPatterns #-}
+
 -- | The Misc module contains helper functions that seem out of place
 --   anywhere else.
-module Misc
+--
+module Misc (
+  all_equal,
+  disjoint,
+  factorial,
+  flatten,
+  misc_properties,
+  misc_tests,
+  transpose_xz )
 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
+import qualified Data.Vector as V ( Vector, elem, empty, filter )
+import Test.Tasty ( TestTree, testGroup )
+import Test.Tasty.HUnit ( Assertion, assertEqual, testCase )
+import Test.Tasty.QuickCheck ( Property, (==>), testProperty )
 
 
 -- | The standard factorial function. See
@@ -25,12 +32,13 @@ import Test.QuickCheck
 --   24
 --
 factorial :: Int -> Int
-factorial !n
-    | n > 20    = error "integer overflow in factorial function"
-    | otherwise = go 1 n
-    where go !acc !i
-                | i <= 1    = acc
-                | otherwise = go (acc * i) (i - 1)
+factorial !n =
+  go 1 n
+  where
+    go :: Int -> Int -> Int
+    go !acc !i
+      | i <= 1    = acc
+      | otherwise = go (acc * i) (i - 1)
 
 -- | Takes a three-dimensional list, and flattens it into a
 --   one-dimensional one.
@@ -64,11 +72,9 @@ transpose_xz m =
 --   Only used in tests.
 --
 all_equal :: (Eq a) => [a] -> Bool
-all_equal xs =
-    all (== first_element) other_elements
-    where
-      first_element  = head xs
-      other_elements = tail xs
+all_equal [] = True -- Vacuously
+all_equal (x:xs) = all (== x) xs
+
 
 
 -- | Returns 'True' if the vectors xs and ys are disjoint, 'False'
@@ -105,17 +111,17 @@ test_flatten1 =
     assertEqual "flatten actually works" expected_list actual_list
     where
       target = [[[1::Int]], [[2, 3]]]
-      expected_list = [1, 2, 3]
+      expected_list = [1, 2, 3] :: [Int]
       actual_list = flatten target
 
 
-misc_tests :: Test.Framework.Test
+misc_tests :: TestTree
 misc_tests =
-    testGroup "Misc Tests" [
+    testGroup "Misc tests" [
       testCase "flatten (1)" test_flatten1 ]
 
 
-misc_properties :: Test.Framework.Test
+misc_properties :: TestTree
 misc_properties =
-    testGroup "Misc Properties" [
+    testGroup "Misc properties" [
       testProperty "factorial greater" prop_factorial_greater ]