module Exercise_4 where import Data.List {-H4.1.10-} zero :: Int -> Int -> [[Int]] zero n m = (replicate m (replicate n 0)) dimensions :: [[a]] -> (Int,Int) dimensions xs = if null xs then (0,0) else if and [length (head xs) == length x | x <- xs] then (length xs, length (head xs)) else (-1,-1) setElem :: Int -> (Int, Int) -> [[Int]] -> [[Int]] setElem newVal (i, j) m | j >= fst (dimensions m) || i >= snd (dimensions m) = [[i, j], [snd (dimensions m), fst (dimensions m)]] | otherwise = take j m ++ [(take i (m!!j) ++ [newVal] ++ drop (i + 1) (m!!j))] ++ drop (j + 1) m getElem :: Int -> Int -> [[Int]] -> Int getElem i j m = (m!!j)!!i optionChecker :: Eq a => [a] -> [a] -> (Int, Int) -> Int -> Int -> [[Int]] -> Int optionChecker a b (0, 0) c t m = 0 optionChecker a b (i, j) 0 t m | i > 0 = optionChecker a b (i, j) 1 ((getElem (i - 1) j m) + 1) m | otherwise = optionChecker a b (i, j) 1 t m optionChecker a b (i, j) 1 t m | j > 0 = optionChecker a b (i, j) 2 (min t ((getElem i (j - 1) m) + 1)) m | otherwise = optionChecker a b (i, j) 2 t m optionChecker a b (i, j) 2 t m | i > 0 && j > 0 && (a!!(i - 1)) == (b!!(j - 1)) = optionChecker a b (i, j) 3 (min t (getElem (i - 1) (j - 1) m)) m | otherwise = optionChecker a b (i, j) 3 t m optionChecker a b (i, j) 3 t m | i > 0 && j > 0 && not ((a!!(i - 1)) == (b!!(j - 1))) = optionChecker a b (i, j) 4 (min t ((getElem (i - 1) (j - 1) m) + 1)) m | otherwise = optionChecker a b (i, j) 4 t m optionChecker a b (i, j) 4 t m | i > 1 && j > 1 && (a!!(i - 1)) == (b!!(j - 2)) && (a!!(i - 2)) == (b!!(j - 1)) = min t ((getElem (i - 2) (j - 2) m) + 1) | otherwise = t meditDistance :: Eq a => [a] -> [a] -> [[Int]] meditDistance a b = helper a b 0 0 (zero (length a + 1) (length b + 1)) where helper u v i j m | j >= length v + 1= m | i >= length u + 1 && j < length v + 1 = helper u v 0 (j + 1) m | otherwise = helper u v (i + 1) j (setElem (optionChecker a b (i,j) 0 100 m) (i,j) m) editDistance :: Eq a => [a] -> [a] -> Int editDistance [] [] = 0 editDistance _ [] = 0 editDistance [] _ = 0 editDistance a b = helper a b 0 0 (zero (length a + 1) (length b + 1)) where helper u v i j m | j >= length v + 1 = (getElem (length u) (length v) m) | i >= length u + 1 && j < length v + 1 = helper u v 0 (j + 1) m | otherwise = helper u v (i + 1) j (setElem (optionChecker a b (i,j) 0 100 m) (i, j) m) minimalDistances :: [String] -> String -> [String] minimalDistances ds x = helper [(d, (editDistance d x)) | d <- ds] where helper m = [fst y | y <- m, snd y == minimum (snd (unzip m))] {-H4.1.11-} {-WETT-} spellCorrect :: [String] -> [String] -> [[String]] spellCorrect d [] = [] spellCorrect d (x:xs) = (minimalDistances d x):(spellCorrect d xs) {-TTEW-}