module Text.Fuzzy.Levenshtein where
import Data.List (sortOn)
import Data.Text (Text)
import qualified Data.Text as T
import Text.EditDistance
import Text.Fuzzy.Parallel
levenshteinScored :: Int -> Text -> [Text] -> [Scored Text]
levenshteinScored :: Int -> Text -> [Text] -> [Scored Text]
levenshteinScored Int
chunkSize Text
needle [Text]
haystack = do
let levenshtein :: String -> String -> Int
levenshtein = EditCosts -> String -> String -> Int
levenshteinDistance (EditCosts -> String -> String -> Int)
-> EditCosts -> String -> String -> Int
forall a b. (a -> b) -> a -> b
$ EditCosts
defaultEditCosts {substitutionCosts=ConstantCost 2}
(Scored Text -> Int) -> [Scored Text] -> [Scored Text]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Scored Text -> Int
forall a. Scored a -> Int
score ([Scored Text] -> [Scored Text]) -> [Scored Text] -> [Scored Text]
forall a b. (a -> b) -> a -> b
$
Int
-> Text
-> [Text]
-> (Text -> Text)
-> (Text -> Text -> Maybe Int)
-> [Scored Text]
forall t.
Int
-> Text
-> [t]
-> (t -> Text)
-> (Text -> Text -> Maybe Int)
-> [Scored t]
matchPar Int
chunkSize Text
needle [Text]
haystack Text -> Text
forall a. a -> a
id ((Text -> Text -> Maybe Int) -> [Scored Text])
-> (Text -> Text -> Maybe Int) -> [Scored Text]
forall a b. (a -> b) -> a -> b
$
\Text
a Text
b -> Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ String -> String -> Int
levenshtein (Text -> String
T.unpack Text
a) (Text -> String
T.unpack Text
b)