module Tests where import Numeric.Vector import Numeric.Matrix import Numeric.MatrixList import Numeric.Function import Numeric.Statistics.LDA import Test.HUnit ( Test (..), assertEqual, runTestTT ) {----------------------------------------------------------------- -------------------- Init Testdata ------------------------------- -----------------------------------------------------------------} testMatrix :: [Matrix Double] testMatrix = [testMatrix_A,testMatrix_B] testMatrix_A :: Matrix Double testMatrix_A = fromLists testdata_A testMatrix_B :: Matrix Double testMatrix_B = fromLists testdata_B testdata :: RawMatrixList Double testdata = [testdata_A,testdata_B] -- [[1_Attribute1, ..., 1_AttributeN], ..., [N_Attribute1, ..., N_AttributeN]] testdata_A :: RawMatrix Double testdata_A = [[2,3],[3,4],[6,5],[4,4],[3,2],[4,7],[3,5],[2,4],[5,6],[3,6],[3,3],[4,5]] testdata_B :: RawMatrix Double testdata_B = [[5,4],[4,3],[7,5],[3,3],[4,4],[5,2],[4,2],[5,5],[6,7],[5,3],[6,4],[6,6]] {----------------------------------------------------------------- -------------------- Testing Matrix Module ----------------------- -----------------------------------------------------------------} test_eigenvalue = TestCase ( assertEqual "Testing eigenvalue-function" 0.9122456375784809 ( eigenvalue (fromLists [[0.77143,-0.25714],[-0.42245,0.14082]]) ) ) test_eigenvector = TestCase ( assertEqual "Testing eigenvector-function" [0.8770950095147589,-0.48031692067249215] (toList.eigenvector $ (fromLists [[-0.14081563757848092,-0.25714],[-0.42245,-0.7714256375784809]])) ) test_reduceMatrix = TestCase ( assertEqual "Testing reduceMatrix-function" ([[ -0.14081563757848092, -0.25714], [-0.42245, -0.7714256375784809 ]]) ( Numeric.Matrix.toLists.reduceMatrix $ (fromLists [[0.77143,-0.25714],[-0.42245,0.14082]]) ) ) {----------------------------------------------------------------- -------------------- Testing MatrixList Module ----------------------- -----------------------------------------------------------------} test_averages = TestCase ( assertEqual "Testing averages-function" [[2.5,3.5,5.5,4.0,2.5,5.5,4.0,3.0,5.5,4.5,3.0,4.5],[4.5,3.5,6.0,3.0,4.0,3.5,3.0,5.0,6.5,4.0,5.0,6.0]] (averages testdata)) {----------------------------------------------------------------- -------------------- Testing LDA Module -------------------------- -----------------------------------------------------------------} test_fisher = TestCase ( assertEqual "Testing fisher-function" 0 (fisher testdata [2,3])) test_fisherAll = TestCase ( assertEqual "Testing fisherAll-function" [[0,0,1,0,0,0,0,0,0,0,0,0],[1,1,1,0,0,1,1,1,1,1,1,1]] (fisherAll testdata)) test_fisherClassificationFunction = TestCase ( assertEqual "Testing fisherClassificationFunction-function" [[-6.5972288132130075,1.7285714285714286,1.279591836734694],[-10.222739017294638,3.614285714285714,0.246938775510204]] (fisherClassificationFunction testdata)) test_aprioriProbability = TestCase ( assertEqual "Testing aprioriProbability-function" [0.5,0.5] (aprioriProbability testdata)) test_discriminantCriteria = TestCase ( assertEqual "Testing discriminantCriteria-function" [0.9122448979591838,0.9122448979591834] (discriminantCriteria testdata)) test_isolatedDiscriminant = TestCase ( assertEqual "Testing isolatedDiscriminant-function" [0.46551724137931033,3.0612244897959183e-2] (isolatedDiscriminant testdata)) tests = TestList [ TestLabel "Test eigenvalue" test_eigenvalue, TestLabel "Test eigenvector" test_eigenvector, TestLabel "Test reduceMatrix" test_reduceMatrix, TestLabel "Test averages" test_averages, TestLabel "Test fisher" test_fisher, TestLabel "Test fisherAll" test_fisherAll, TestLabel "Test fisherClassificationFunction" test_fisherClassificationFunction, TestLabel "Test aprioriProbability" test_aprioriProbability, TestLabel "Test discriminantCriteria" test_discriminantCriteria, TestLabel "Test isolatedDiscriminant"test_isolatedDiscriminant] main = runTestTT tests