]> gitweb.michael.orlitzky.com - spline3.git/blob - src/Misc.hs
Comment some test-only functions.
[spline3.git] / src / Misc.hs
1 {-# LANGUAGE BangPatterns #-}
2 -- | The Misc module contains helper functions that seem out of place
3 -- anywhere else.
4 module Misc
5 where
6
7 import qualified Data.Vector as V (Vector, elem, empty, filter)
8 import Test.Framework (Test, testGroup)
9 import Test.Framework.Providers.HUnit (testCase)
10 import Test.Framework.Providers.QuickCheck2 (testProperty)
11 import Test.HUnit (Assertion, assertEqual)
12 import Test.QuickCheck
13
14
15 -- | The standard factorial function. See
16 -- <http://www.willamette.edu/~fruehr/haskell/evolution.html> for
17 -- possible improvements.
18 --
19 -- Examples:
20 --
21 -- >>> factorial 0
22 -- 1
23 --
24 -- >>> factorial 4
25 -- 24
26 --
27 factorial :: Int -> Int
28 factorial !n
29 | n > 20 = error "integer overflow in factorial function"
30 | otherwise = go 1 n
31 where go !acc !i
32 | i <= 1 = acc
33 | otherwise = go (acc * i) (i - 1)
34
35 -- | Takes a three-dimensional list, and flattens it into a
36 -- one-dimensional one.
37 --
38 -- Examples:
39 --
40 -- >>> flatten [ [[1,2], [3,4]], [[5,6], [7,8]] ]
41 -- [1,2,3,4,5,6,7,8]
42 --
43 flatten :: [[[a]]] -> [a]
44 flatten xs = concat $ concat xs
45
46
47 -- | Switch the x and z dimensions of a three-dimensional list.
48 transpose_xz :: [[[a]]] -> [[[a]]]
49 transpose_xz [] = []
50 transpose_xz [[]] = [[]]
51 transpose_xz [[[]]] = [[[]]]
52 transpose_xz m =
53 [[[ m !! x !! y !! z | x <- [0..xsize]]
54 | y <- [0..ysize]]
55 | z <- [0..zsize]]
56 where
57 zsize = (length m) - 1
58 ysize = length (head m) - 1
59 xsize = length (head $ head m) - 1
60
61 -- | Takes a list, and returns True if its elements are pairwise
62 -- equal. Returns False otherwise.
63 --
64 -- Only used in tests.
65 --
66 all_equal :: (Eq a) => [a] -> Bool
67 all_equal xs =
68 all (== first_element) other_elements
69 where
70 first_element = head xs
71 other_elements = tail xs
72
73
74 -- | Returns 'True' if the vectors xs and ys are disjoint, 'False'
75 -- otherwise.
76 --
77 -- Examples:
78 --
79 -- >>> let xs = Data.Vector.fromList [1,2,3]
80 -- >>> let ys = Data.Vector.fromList [4,5,6]
81 -- >>> disjoint xs ys
82 -- True
83 --
84 -- >>> let ys = Data.Vector.fromList [3,4,5]
85 -- >>> disjoint xs ys
86 -- False
87 --
88 -- Only used in tests.
89 --
90 disjoint :: (Eq a) => V.Vector a -> V.Vector a -> Bool
91 disjoint xs ys =
92 intersect xs ys == V.empty
93 where
94 intersect :: (Eq a) => V.Vector a -> V.Vector a -> V.Vector a
95 intersect ws zs =
96 V.filter (`V.elem` zs) ws
97
98 prop_factorial_greater :: Int -> Property
99 prop_factorial_greater n =
100 n <= 20 ==> factorial n >= n
101
102
103 test_flatten1 :: Assertion
104 test_flatten1 =
105 assertEqual "flatten actually works" expected_list actual_list
106 where
107 target = [[[1::Int]], [[2, 3]]]
108 expected_list = [1, 2, 3]
109 actual_list = flatten target
110
111
112 misc_tests :: Test.Framework.Test
113 misc_tests =
114 testGroup "Misc Tests" [
115 testCase "flatten (1)" test_flatten1 ]
116
117
118 misc_properties :: Test.Framework.Test
119 misc_properties =
120 testGroup "Misc Properties" [
121 testProperty "factorial greater" prop_factorial_greater ]