module Exercise_4 where import Data.List import Data.Maybe import Data.Function infixr 9 <.> (<.>) :: Functor f => (a -> b) -> (x -> f a) -> (x -> f b) (<.>) l r v = l <$> (r v) equals :: Eq a => a -> a -> Bool equals = (==) headM :: [a] -> Maybe a headM [] = Nothing headM (a:_) = Just a orElse :: Maybe a -> a -> a orElse (Just a) _ = a orElse Nothing a = a {-H4.1.10-} when :: Bool -> a -> Maybe a when True x = Just x when False _ = Nothing editDistance :: Eq a => [a] -> [a] -> Int editDistance (a1:a2:as) (b1:b2:bs) = minimum $ catMaybes [ Just $ editDistance (a2:as) (b1:b2:bs) + 1 , Just $ editDistance (a1:a2:as) (b2:bs) + 1 , when (a1 == b1) $ editDistance (a2:as) (b2:bs) , when (a1 /= b1) $ editDistance (a2:as) (b2:bs) + 1 , when (a1 == b2 && a2 == b1) $ editDistance as bs + 1 ] editDistance (a:as) (b:bs) = if (a == b) then editDistance as bs else minimum [ editDistance as bs + 1 , editDistance (a:as) bs + 1 , editDistance as (b:bs) + 1 ] editDistance [] [] = 0 editDistance l [] = length l editDistance [] r = length r {-H4.1.11-} {-WETT-} best :: (a -> a -> Int) -> [a] -> a -> ([a], Int) best f [] val = ([], maxBound) best f (o:os) val = if thisRes < otherRes then ([o], thisRes) else if thisRes == otherRes then (o:peers, thisRes) else (peers, otherRes) where thisRes = f o val (peers, otherRes) = best f os val spellCorrect :: [String] -> [String] -> [[String]] spellCorrect d xs = map (fst . best editDistance d) xs {-TTEW-}