241 lines
7.5 KiB
Haskell
241 lines
7.5 KiB
Haskell
|
module Test3 where
|
||
|
|
||
|
import Angabe3
|
||
|
import Test.Tasty
|
||
|
import Test.Tasty.HUnit
|
||
|
import Test.Tasty.Ingredients (composeReporters)
|
||
|
import Test.Tasty.Ingredients.ConsoleReporter (consoleTestReporter)
|
||
|
import Control.Exception (ErrorCall(ErrorCallWithLocation), try, evaluate)
|
||
|
|
||
|
main :: IO ()
|
||
|
main = defaultMainWithIngredients [consoleTestReporter] spec
|
||
|
|
||
|
{-----TESTDATEN BEGINN-----}
|
||
|
m1 = M [[1,2],[3,4]] :: Matrix
|
||
|
m2 = M [[1,2],[3,4],[5,6]] :: Matrix
|
||
|
m3 = M [[1,2,3],[4,5],[6]] :: Matrix
|
||
|
m4 = M [[1,2,3],[],[6]] :: Matrix
|
||
|
m5 = M [[],[],[]] :: Matrix
|
||
|
m6 = M [] :: Matrix
|
||
|
m7 = M [[1,2,5],[-3,-4,1]] :: Matrix
|
||
|
m8 = M [[4,4],[1,0],[9,6]] :: Matrix
|
||
|
m9 = M [[-1,1],[1,-1],[-2,2]] :: Matrix
|
||
|
m10 = M [[0,0,0],[0,0,0],[0,0,0]] :: Matrix
|
||
|
neg_m1 = M [[-1,-2],[-3,-4]] :: Matrix
|
||
|
neg_m7 = M[[-1,-2,-5],[3,4,-1]] :: Matrix
|
||
|
abs_m7 = M [[1,2,5],[3,4,1]] :: Matrix
|
||
|
|
||
|
errMsg_gleich = "Gleichheit undefiniert" :: String
|
||
|
errMsg_ungleich = "Ungleichheit undefiniert" :: String
|
||
|
errMsg_signum = "Vorzeichenfunktion undefiniert" :: String
|
||
|
{-----TESTDATEN ENDE-----}
|
||
|
|
||
|
getMsg :: ErrorCall -> String
|
||
|
getMsg (ErrorCallWithLocation msg _) = msg
|
||
|
|
||
|
assertError :: (Show a) => String -> a -> IO ()
|
||
|
assertError errorMsg action = do
|
||
|
r <- try (evaluate action)
|
||
|
case r of
|
||
|
Left e -> if (getMsg e == errorMsg) then return()
|
||
|
else assertFailure $ "Received unexpected error: " ++ (show e) ++ "\ninstead of: " ++ errorMsg
|
||
|
Right _ -> assertFailure $ "Expected error: " ++ errorMsg
|
||
|
|
||
|
spec :: TestTree
|
||
|
spec =
|
||
|
testGroup
|
||
|
"Test2 Spec"
|
||
|
[
|
||
|
showMatrix_tests,
|
||
|
matrixtyp_tests,
|
||
|
gleichheit_tests,
|
||
|
plus_tests,
|
||
|
minus_tests,
|
||
|
mal_tests,
|
||
|
negate_tests,
|
||
|
abs_tests,
|
||
|
signum_tests,
|
||
|
fromInteger_tests
|
||
|
]
|
||
|
|
||
|
showMatrix_tests :: TestTree
|
||
|
showMatrix_tests =
|
||
|
testGroup
|
||
|
"-----show Matrix Tests-----"
|
||
|
[
|
||
|
testCase "m1: M [[1,2] [3,4]]" $
|
||
|
show m1 @?= "([1,2] [3,4])",
|
||
|
testCase "m2: M [[1,2],[3,4],[5,6]]" $
|
||
|
show m2 @?= "([1,2] [3,4] [5,6])",
|
||
|
testCase "m3: M [[1,2,3],[4,5],[6]]" $
|
||
|
show m3 @?= "([1,2,3] [4,5] [6])",
|
||
|
testCase "m4: M [[1,2,3],[],[6]]" $
|
||
|
show m4 @?= "([1,2,3] [] [6])",
|
||
|
testCase "m5: M [[],[],[]]" $
|
||
|
show m5 @?= "([] [] [])",
|
||
|
testCase "m6: M []" $
|
||
|
show m6 @?= show fehlerwert
|
||
|
]
|
||
|
|
||
|
matrixtyp_tests :: TestTree
|
||
|
matrixtyp_tests =
|
||
|
testGroup
|
||
|
"-----Matrixtyp Tests-----"
|
||
|
[
|
||
|
testCase "m1: quadratische Matrix (2,2)" $
|
||
|
matrixtyp m1 @?= Mat (2,2),
|
||
|
testCase "m2: rechteckige Matrix (3,2)" $
|
||
|
matrixtyp m2 @?= Mat (3,2),
|
||
|
testCase "m5: leer-elementrige Matrix" $
|
||
|
matrixtyp m5 @?= KeineMatrix,
|
||
|
testCase "m6: fehlerwertige Matrix (M [])" $
|
||
|
matrixtyp m6 @?= KeineMatrix,
|
||
|
testCase "m3: ungültige Matrix, kein Leer-Element" $
|
||
|
matrixtyp m3 @?= KeineMatrix,
|
||
|
testCase "m4: ungültige Matrix, ein Leer-Element" $
|
||
|
matrixtyp m4 @?= KeineMatrix
|
||
|
]
|
||
|
|
||
|
gleichheit_tests :: TestTree
|
||
|
gleichheit_tests =
|
||
|
testGroup
|
||
|
"-----Matrix-Gleichheit Tests-----"
|
||
|
[
|
||
|
testCase "m1 == m1: gültige gleiche Matrizen" $
|
||
|
m1 == m1 @?= True,
|
||
|
testCase "m1 == m2: gültige ungleich-zeilige Matrizen" $
|
||
|
m1 == m2 @?= False,
|
||
|
testCase "m1 == m2: gültige ungleich-spaltige Matrizen" $
|
||
|
m1 == m7 @?= False,
|
||
|
testCase "m5 /= m5: leer-elementrige Matrizen" $
|
||
|
assertError errMsg_ungleich (m5 /= m5),
|
||
|
testCase "m3 == m1: linke Matrix ungültig" $
|
||
|
assertError errMsg_gleich (m3 == m1),
|
||
|
testCase "m1 /= m3: rechte Matrix ungültig" $
|
||
|
assertError errMsg_ungleich (m1 /= m3),
|
||
|
testCase "m3 == m4: beide Matrizen ungültig" $
|
||
|
assertError errMsg_gleich (m3 == m4),
|
||
|
testCase "m6 /= m6: beide Matrizen fehlerwertig (M [])" $
|
||
|
assertError errMsg_ungleich (m6 /= m6)
|
||
|
]
|
||
|
|
||
|
plus_tests :: TestTree
|
||
|
plus_tests =
|
||
|
testGroup
|
||
|
"-----Matrix-Summe Tests-----"
|
||
|
[
|
||
|
testCase "m1 + m1: gültige Matrizen, Summe definiert" $
|
||
|
m1 + m1 @?= M [[2,4],[6,8]],
|
||
|
testCase "m1 + m2: gültige Matrizen, Summe undefiniert" $
|
||
|
show (m1 + m2) @?= show fehlerwert,
|
||
|
testCase "m1 + m4: rechte Matrix ungültig" $
|
||
|
show (m1 + m4) @?= show fehlerwert,
|
||
|
testCase "m4 + m1: linke Matrix ungültig" $
|
||
|
show (m4 + m1) @?= show fehlerwert,
|
||
|
testCase "m3 + m4: beide Matrizen ungültig" $
|
||
|
show (m3 + m4) @?= show fehlerwert,
|
||
|
testCase "m5 + m5: leere Matrizen, Summe undefiniert" $
|
||
|
show (m5 + m5) @?= show fehlerwert,
|
||
|
testCase "m6 + m7: linke Matrix fehlerwertig (M [])" $
|
||
|
show (m6 + m7) @?= show fehlerwert
|
||
|
]
|
||
|
|
||
|
minus_tests :: TestTree
|
||
|
minus_tests =
|
||
|
testGroup
|
||
|
"-----Matrix-Differenz Tests-----"
|
||
|
[
|
||
|
testCase "m1 - m1: gültige Matrizen, Differenz definiert" $
|
||
|
m1 - m1 @?= M [[0,0],[0,0]],
|
||
|
testCase "m2 - m8: gültige Matrizen, Differenz definiert, neg. Werte" $
|
||
|
m2 - m8 @?= M [[-3,-2],[2,4],[-4,0]],
|
||
|
testCase "m1 - m2: gültige Matrizen, Differenz undefiniert" $
|
||
|
show (m1 - m2) @?= show fehlerwert,
|
||
|
testCase "m1 - m4: rechte Matrix ungültig" $
|
||
|
show (m1 - m4) @?= show fehlerwert,
|
||
|
testCase "m4 - m1: linke Matrix ungültig" $
|
||
|
show (m4 - m1) @?= show fehlerwert,
|
||
|
testCase "m3 - m4: beide Matrizen ungültig" $
|
||
|
show (m3 - m4) @?= show fehlerwert,
|
||
|
testCase "m5 - m5: leere Matrizen, Differenz undefiniert" $
|
||
|
show (m5 - m5) @?= show fehlerwert,
|
||
|
testCase "m6 - m7: linke Matrix fehlerwertig (M [])" $
|
||
|
show (m6 - m7) @?= show fehlerwert
|
||
|
]
|
||
|
|
||
|
mal_tests :: TestTree
|
||
|
mal_tests =
|
||
|
testGroup
|
||
|
"-----Matrix-Multiplikation Tests-----"
|
||
|
[
|
||
|
testCase "m2 * m7: gültige Matrizen, gültiger Typ" $
|
||
|
m2 * m7 @?= M [[-5,-6,7],[-9,-10,19],[-13,-14,31]],
|
||
|
testCase "m1 * m2: gültige Matrizen, ungültiger Typ" $
|
||
|
show (m1 * m2) @?= show fehlerwert,
|
||
|
testCase "m5 * m5: leere Matrizen" $
|
||
|
show (m5 * m5) @?= show fehlerwert,
|
||
|
testCase "m6 * m7: linke Matrix fehlerwertig (M [])" $
|
||
|
show (m6 * m7) @?= show fehlerwert
|
||
|
]
|
||
|
|
||
|
negate_tests :: TestTree
|
||
|
negate_tests =
|
||
|
testGroup
|
||
|
"-----Negate Tests-----"
|
||
|
[
|
||
|
testCase "m1: gültige nur positive VZ Matrix" $
|
||
|
negate m1 @?= neg_m1,
|
||
|
testCase "m7: gültige gemischte VZ Matrix" $
|
||
|
negate m7 @?= neg_m7,
|
||
|
testCase "m5: leere Matrix" $
|
||
|
show (negate m5) @?= show fehlerwert,
|
||
|
testCase "m4: ungültige Matrix" $
|
||
|
show (negate m4) @?= show fehlerwert
|
||
|
]
|
||
|
|
||
|
abs_tests :: TestTree
|
||
|
abs_tests =
|
||
|
testGroup
|
||
|
"-----Abs.Betrag Tests-----"
|
||
|
[
|
||
|
testCase "m7: gültige gemischte VZ Matrix" $
|
||
|
abs m7 @?= abs_m7,
|
||
|
testCase "m5: leere Matrix" $
|
||
|
show (abs m5) @?= show fehlerwert,
|
||
|
testCase "m4: ungültige Matrix" $
|
||
|
show (abs m4) @?= show fehlerwert
|
||
|
]
|
||
|
|
||
|
signum_tests :: TestTree
|
||
|
signum_tests =
|
||
|
testGroup
|
||
|
"-----Signum Tests-----"
|
||
|
[
|
||
|
testCase "m1: gültige nur positive VZ Matrix" $
|
||
|
signum m1 @?= M [[1]],
|
||
|
testCase "m7: gültige gemischte VZ Matrix" $
|
||
|
assertError errMsg_signum (signum m7),
|
||
|
testCase "neg_m1: gültige nur negative VZ Matrix" $
|
||
|
signum neg_m1 @?= M [[-1]],
|
||
|
testCase "m10: gültige Matrix, alle Einträge 0" $
|
||
|
signum m10 @?= M[[0]],
|
||
|
testCase "m5: leere Matrix" $
|
||
|
assertError errMsg_signum (signum m5),
|
||
|
testCase "m4: ungültige Matrix" $
|
||
|
assertError errMsg_signum (signum m4),
|
||
|
testCase "m9: gültige gemischte VZ Matrix, Summe negVZ == Summe posVZ" $
|
||
|
assertError errMsg_signum (signum m9)
|
||
|
]
|
||
|
|
||
|
fromInteger_tests :: TestTree
|
||
|
fromInteger_tests =
|
||
|
testGroup
|
||
|
"-----fromInteger Tests-----"
|
||
|
[
|
||
|
testCase "fromInteger 1" $
|
||
|
fromInteger 1 @?= M [[1]],
|
||
|
testCase "fromInteger 0" $
|
||
|
fromInteger 0 @?= M [[0]],
|
||
|
testCase "fromInteger -1" $
|
||
|
fromInteger (-1) @?= M [[-1]]
|
||
|
]
|