summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--AufgabeFFP8.hs35
-rw-r--r--TestAufgabeFFP8.hs165
2 files changed, 183 insertions, 17 deletions
diff --git a/AufgabeFFP8.hs b/AufgabeFFP8.hs
index d328ae8..fe9c894 100644
--- a/AufgabeFFP8.hs
+++ b/AufgabeFFP8.hs
@@ -96,26 +96,27 @@ divideAndConquer indiv solve divide combine initPb = dAC initPb
96 96
97-- minfree basic daq higher order 97-- minfree basic daq higher order
98 98
99b_indiv :: Int -> [Int] -> Bool 99minfree_bhof :: [Int] -> Int
100b_indiv l xs = length xs < l 100minfree_bhof xs = divideAndConquer b_indiv b_solve b_divide b_combine (False, xs)
101 101
102b_solve :: [Int] -> [Int] 102b_indiv :: (Bool, [Int]) -> Bool
103b_solve = id 103b_indiv (b, _) = b
104 104
105b_divide :: Int -> [Int] -> [[Int]] 105b_solve :: (Bool, [Int]) -> Int
106b_divide b xs = [us, vs] 106b_solve (_, xs) = head xs
107 where (us,vs) = partition (<b) xs 107
108 108
109b_combine :: Int -> [Int] -> [[Int]] -> [Int] 109
110b_combine b _ (us:vs:[]) = if (null ([0..b-1] \\ us)) 110b_divide :: (Bool, [Int]) -> [(Bool, [Int])]
111 then ([b..] \\ vs) 111b_divide (n, xs) = if (null ([0..b-1] \\ us))
112 else ([0..] \\ us) 112 then [(True, [b..] \\ vs)]
113 113 else [(True, [0..] \\ us)]
114minfree_bhof :: [Int] -> Int 114 where
115minfree_bhof [] = 0 115 (us, vs) = partition (<b) xs
116minfree_bhof xs = head $ divideAndConquer (b_indiv (length xs)) b_solve (b_divide b) (b_combine b) xs 116 b = 1 + (length xs) `div` 2
117 where b = 1+(length xs) `div` 2
118 117
118b_combine :: (Bool, [Int]) -> [Int] -> Int
119b_combine xs sols = head sols
119 120
120-- minfree refined daq higher order 121-- minfree refined daq higher order
121 122
diff --git a/TestAufgabeFFP8.hs b/TestAufgabeFFP8.hs
new file mode 100644
index 0000000..6e1e5a1
--- /dev/null
+++ b/TestAufgabeFFP8.hs
@@ -0,0 +1,165 @@
1#!/usr/bin/runhugs +l
2
3module Main where
4
5import Test.HUnit
6import Control.Monad
7import System
8import AufgabeFFP8
9import Test.QuickCheck
10import System.IO.Unsafe
11
12---------------------------------
13-- Instanzen
14
15a :: [Int]
16a = []
17
18b :: [Int]
19b = [0]
20
21c :: [Int]
22c = [1]
23
24d :: [Int]
25d = [2,0,1]
26
27e :: [Int]
28e = [1,2,3]
29
30f :: [Int]
31f = [0,1,2,3,5]
32
33g :: [Int]
34g = [5,0,1,3,2]
35
36h :: [Int]
37h = [0..1000]
38
39l :: [Int]
40l = [0..4000]
41
42---------------------------------
43cases1 = "minfree_bv" ~: TestList [
44 "minfree_bv a" ~: 0 ~=? (minfree_bv a),
45 "minfree_bv b" ~: 1 ~=? (minfree_bv b),
46 "minfree_bv c" ~: 0 ~=? (minfree_bv c),
47 "minfree_bv d" ~: 3 ~=? (minfree_bv d),
48 "minfree_bv e" ~: 0 ~=? (minfree_bv e),
49 "minfree_bv f" ~: 4 ~=? (minfree_bv f),
50 "minfree_bv g" ~: 4 ~=? (minfree_bv g),
51 "minfree_bv h" ~: 1001 ~=? (minfree_bv h),
52 "minfree_bv l" ~: 4001 ~=? (minfree_bv l)
53 ]
54
55cases2 = "minfree_chl" ~: TestList [
56 "minfree_chl a" ~: 0 ~=? (minfree_chl a),
57 "minfree_chl b" ~: 1 ~=? (minfree_chl b),
58 "minfree_chl c" ~: 0 ~=? (minfree_chl c),
59 "minfree_chl d" ~: 3 ~=? (minfree_chl d),
60 "minfree_chl e" ~: 0 ~=? (minfree_chl e),
61 "minfree_chl f" ~: 4 ~=? (minfree_chl f),
62 "minfree_chl g" ~: 4 ~=? (minfree_chl g),
63 "minfree_chl h" ~: 1001 ~=? (minfree_chl h),
64 "minfree_chl l" ~: 4001 ~=? (minfree_chl l)
65 ]
66
67cases3 = "minfree_col" ~: TestList [
68 "minfree_col a" ~: 0 ~=? (minfree_col a),
69 "minfree_col b" ~: 1 ~=? (minfree_col b),
70 "minfree_col c" ~: 0 ~=? (minfree_col c),
71 "minfree_col d" ~: 3 ~=? (minfree_col d),
72 "minfree_col e" ~: 0 ~=? (minfree_col e),
73 "minfree_col f" ~: 4 ~=? (minfree_col f),
74 "minfree_col g" ~: 4 ~=? (minfree_col g),
75 "minfree_col h" ~: 1001 ~=? (minfree_col h),
76 "minfree_col l" ~: 4001 ~=? (minfree_col l)
77 ]
78
79cases4 = "minfree_b" ~: TestList [
80 "minfree_b a" ~: 0 ~=? (minfree_b a),
81 "minfree_b b" ~: 1 ~=? (minfree_b b),
82 "minfree_b c" ~: 0 ~=? (minfree_b c),
83 "minfree_b d" ~: 3 ~=? (minfree_b d),
84 "minfree_b e" ~: 0 ~=? (minfree_b e),
85 "minfree_b f" ~: 4 ~=? (minfree_b f),
86 "minfree_b g" ~: 4 ~=? (minfree_b g),
87 "minfree_b h" ~: 1001 ~=? (minfree_b h),
88 "minfree_b l" ~: 4001 ~=? (minfree_b l)
89 ]
90
91cases5 = "minfree_r" ~: TestList [
92 "minfree_r a" ~: 0 ~=? (minfree_r a),
93 "minfree_r b" ~: 1 ~=? (minfree_r b),
94 "minfree_r c" ~: 0 ~=? (minfree_r c),
95 "minfree_r d" ~: 3 ~=? (minfree_r d),
96 "minfree_r e" ~: 0 ~=? (minfree_r e),
97 "minfree_r f" ~: 4 ~=? (minfree_r f),
98 "minfree_r g" ~: 4 ~=? (minfree_r g),
99 "minfree_r h" ~: 1001 ~=? (minfree_r h),
100 "minfree_r l" ~: 4001 ~=? (minfree_r l)
101 ]
102
103cases6 = "minfree_o" ~: TestList [
104 "minfree_o a" ~: 0 ~=? (minfree_o a),
105 "minfree_o b" ~: 1 ~=? (minfree_o b),
106 "minfree_o c" ~: 0 ~=? (minfree_o c),
107 "minfree_o d" ~: 3 ~=? (minfree_o d),
108 "minfree_o e" ~: 0 ~=? (minfree_o e),
109 "minfree_o f" ~: 4 ~=? (minfree_o f),
110 "minfree_o g" ~: 4 ~=? (minfree_o g),
111 "minfree_o h" ~: 1001 ~=? (minfree_o h),
112 "minfree_o l" ~: 4001 ~=? (minfree_o l)
113 ]
114
115cases7 = "minfree_bhof" ~: TestList [
116 "minfree_bhof a" ~: 0 ~=? (minfree_bhof a),
117 "minfree_bhof b" ~: 1 ~=? (minfree_bhof b),
118 "minfree_bhof c" ~: 0 ~=? (minfree_bhof c),
119 "minfree_bhof d" ~: 3 ~=? (minfree_bhof d),
120 "minfree_bhof e" ~: 0 ~=? (minfree_bhof e),
121 "minfree_bhof f" ~: 4 ~=? (minfree_bhof f),
122 "minfree_bhof g" ~: 4 ~=? (minfree_bhof g),
123 "minfree_bhof h" ~: 1001 ~=? (minfree_bhof h),
124 "minfree_bhof l" ~: 4001 ~=? (minfree_bhof l)
125 ]
126
127cases8 = "minfree_rhof" ~: TestList [
128 "minfree_rhof a" ~: 0 ~=? (minfree_rhof a),
129 "minfree_rhof b" ~: 1 ~=? (minfree_rhof b),
130 "minfree_rhof c" ~: 0 ~=? (minfree_rhof c),
131 "minfree_rhof d" ~: 3 ~=? (minfree_rhof d),
132 "minfree_rhof e" ~: 0 ~=? (minfree_rhof e),
133 "minfree_rhof f" ~: 4 ~=? (minfree_rhof f),
134 "minfree_rhof g" ~: 4 ~=? (minfree_rhof g),
135 "minfree_rhof h" ~: 1001 ~=? (minfree_rhof h),
136 "minfree_rhof l" ~: 4001 ~=? (minfree_rhof l)
137 ]
138
139cases9 = "minfree_ohof" ~: TestList [
140 "minfree_ohof a" ~: 0 ~=? (minfree_ohof a),
141 "minfree_ohof b" ~: 1 ~=? (minfree_ohof b),
142 "minfree_ohof c" ~: 0 ~=? (minfree_ohof c),
143 "minfree_ohof d" ~: 3 ~=? (minfree_ohof d),
144 "minfree_ohof e" ~: 0 ~=? (minfree_ohof e),
145 "minfree_ohof f" ~: 4 ~=? (minfree_ohof f),
146 "minfree_ohof g" ~: 4 ~=? (minfree_ohof g),
147 "minfree_ohof h" ~: 1001 ~=? (minfree_ohof h),
148 "minfree_ohof l" ~: 4001 ~=? (minfree_ohof l)
149 ]
150
151---------------------------------
152tests :: [Test]
153tests = [cases1, cases2, cases3, cases4, cases5, cases6]
154
155isSuccess :: Counts -> Bool
156isSuccess Counts{ cases = _, tried = _, errors = 0, failures = 0 } = True
157isSuccess Counts{ cases = _, tried = _, errors = _, failures = _ } = False
158
159runTest :: Test -> IO ()
160runTest test = do
161 result <- runTestTT test
162 unless (isSuccess result) exitFailure
163
164main = do
165 forM tests $ (\test -> runTest test) \ No newline at end of file