module HarmTrace.Matching.Testing where import HarmTrace.Matching.Matching hiding (align, wbMatchF, getDownRight, getMatch, collectMatch) import HarmTrace.Matching.AlignmentFaster import HarmTrace.Matching.Sim import HarmTrace.HAnTree.HAn import Data.Array -- testing import Test.QuickCheck import Data.List.Split import qualified Data.Vector as V -------------------------------------------------------------------------------- -- Testing -------------------------------------------------------------------------------- instance SimInt Char where {- sim 'a' 'b' = 0.5 sim 'a' 'c' = 0.1 sim 'a' 'd' = 1.1 sim 'a' 'e' = -1.1 sim 'a' 'f' = -3.1 sim 'c' 'd' = -1.5 sim 'e' 'f' = 0.5 sim 'g' 'h' = -3.2 sim 'k' 'l' = 4.9 sim 'i' 'j' = 0.95-} simInt a b = if a == b then 5 else 0 instance GetDur Char where getDur _ = 1 data Test = Test Char Int deriving (Eq, Show) instance GetDur Test where getDur (Test _ d) = d instance Arbitrary (Test) where arbitrary = do e <- elements ['a' .. 'm'] d <- elements [1 .. 12] return (Test e d) instance Sim (Test) where {- sim (Test 'a' d) (Test 'b' d2) = 0.5 * durWeight d d2 sim (Test 'b' d) (Test 'a' d2) = 1.5 * durWeight d d2 sim (Test 'a' d) (Test 'c' d2) = -0.5 * durWeight d d2 sim (Test 'a' d) (Test 'd' d2) = 5.5 * durWeight d d2 sim (Test 'd' d) (Test 'b' d2) = -0.5 * durWeight d d2 sim (Test 'e' d) (Test 'f' d2) = 0.5 * durWeight d d2-} sim a b = if a == b then 1.0 else 0.0 -- propRef :: [Char] -> [Char] -> Bool -- -- propRef :: [Test] -> [Test] -> Bool -- propRef a b = (length . fst $ align a b) == (length . fst $ getWeightMatch a b) -- -- propSym :: [Char] -> [Char] -> Bool -- propSym :: [Test] -> [Test] -> Bool -- propSym a b = snd (align a b) == snd (align b a) -- traverse a 2 dimentional array row by row and appies f to every element -- should return a String that is printed to the console pPrintf :: (e -> String) -> Array (Int, Int) e -> IO () pPrintf f n = putStr $ unlines $ map (concatMap (\x -> f x ++ " ")) list where list = splitEvery (fromIntegral (snd $ snd $ bounds n)+1) (elems n) -- pretty prints a 2 diminentional array in a readable format pPrint :: (Show e) => Array (Int, Int) e -> IO () pPrint n = pPrintf show n pPrintV :: Show a => V.Vector (V.Vector a) -> IO () pPrintV = V.mapM_ printLn where printLn :: Show a => V.Vector a -> IO() printLn v = do V.mapM_ (\x -> putStr (show x ++ " ")) v ; putChar '\n' bigTest :: Args bigTest = stdArgs -- Args { replay = Nothing , maxSuccess = 1250 , maxDiscard = 250 , maxSize = 100 }