{-# LANGUAGE FlexibleContexts #-}
module Text.Fuzzy where
import Prelude hiding (filter)
import qualified Prelude as P
import Data.Char (toLower)
import Data.List (sortOn)
import Data.Maybe (isJust, mapMaybe)
import Data.Monoid (mempty, (<>))
import Data.Ord
import Data.String
import qualified Data.Monoid.Textual as T
data (T.TextualMonoid s) => Fuzzy t s =
Fuzzy { forall t s. TextualMonoid s => Fuzzy t s -> t
original :: t
, forall t s. TextualMonoid s => Fuzzy t s -> s
rendered :: s
, forall t s. TextualMonoid s => Fuzzy t s -> Int
score :: Int
} deriving (Int -> Fuzzy t s -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall t s.
(TextualMonoid s, Show t, Show s) =>
Int -> Fuzzy t s -> ShowS
forall t s.
(TextualMonoid s, Show t, Show s) =>
[Fuzzy t s] -> ShowS
forall t s.
(TextualMonoid s, Show t, Show s) =>
Fuzzy t s -> String
showList :: [Fuzzy t s] -> ShowS
$cshowList :: forall t s.
(TextualMonoid s, Show t, Show s) =>
[Fuzzy t s] -> ShowS
show :: Fuzzy t s -> String
$cshow :: forall t s.
(TextualMonoid s, Show t, Show s) =>
Fuzzy t s -> String
showsPrec :: Int -> Fuzzy t s -> ShowS
$cshowsPrec :: forall t s.
(TextualMonoid s, Show t, Show s) =>
Int -> Fuzzy t s -> ShowS
Show, Fuzzy t s -> Fuzzy t s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall t s.
(TextualMonoid s, Eq t, Eq s) =>
Fuzzy t s -> Fuzzy t s -> Bool
/= :: Fuzzy t s -> Fuzzy t s -> Bool
$c/= :: forall t s.
(TextualMonoid s, Eq t, Eq s) =>
Fuzzy t s -> Fuzzy t s -> Bool
== :: Fuzzy t s -> Fuzzy t s -> Bool
$c== :: forall t s.
(TextualMonoid s, Eq t, Eq s) =>
Fuzzy t s -> Fuzzy t s -> Bool
Eq)
{-# INLINABLE match #-}
match :: (T.TextualMonoid s)
=> s
-> t
-> s
-> s
-> (t -> s)
-> Bool
-> Maybe (Fuzzy t s)
match :: forall s t.
TextualMonoid s =>
s -> t -> s -> s -> (t -> s) -> Bool -> Maybe (Fuzzy t s)
match s
pattern t
t s
pre s
post t -> s
extract Bool
caseSensitive =
if forall s. TextualMonoid s => s -> Bool
null s
pat then forall a. a -> Maybe a
Just (forall t s. t -> s -> Int -> Fuzzy t s
Fuzzy t
t s
result Int
totalScore) else forall a. Maybe a
Nothing
where
null :: (T.TextualMonoid s) => s -> Bool
null :: forall s. TextualMonoid s => s -> Bool
null = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
T.any (forall a b. a -> b -> a
const Bool
True)
s :: s
s = t -> s
extract t
t
(Int
totalScore, Int
currScore, s
result, s
pat) =
forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
T.foldl'
forall a. HasCallStack => a
undefined
(\(Int
tot, Int
cur, s
res, s
pat) Char
c ->
case forall t. TextualMonoid t => t -> Maybe (Char, t)
T.splitCharacterPrefix s
pat of
Maybe (Char, s)
Nothing -> (Int
tot, Int
0, s
res forall a. Semigroup a => a -> a -> a
<> forall t. TextualMonoid t => Char -> t
T.singleton Char
c, s
pat)
Just (Char
x, s
xs) ->
if Char -> Char
toLower Char
x forall a. Eq a => a -> a -> Bool
== Char -> Char
toLower Char
c then
let cur' :: Int
cur' = Int
cur forall a. Num a => a -> a -> a
* Int
2 forall a. Num a => a -> a -> a
+ Int
1 in
(Int
tot forall a. Num a => a -> a -> a
+ Int
cur', Int
cur', s
res forall a. Semigroup a => a -> a -> a
<> s
pre forall a. Semigroup a => a -> a -> a
<> forall t. TextualMonoid t => Char -> t
T.singleton Char
c forall a. Semigroup a => a -> a -> a
<> s
post, s
xs)
else (Int
tot, Int
0, s
res forall a. Semigroup a => a -> a -> a
<> forall t. TextualMonoid t => Char -> t
T.singleton Char
c, s
pat)
) (Int
0, Int
0, forall a. Monoid a => a
mempty, s
pattern) s
s
{-# INLINABLE filter #-}
filter :: (T.TextualMonoid s)
=> s
-> [t]
-> s
-> s
-> (t -> s)
-> Bool
-> [Fuzzy t s]
filter :: forall s t.
TextualMonoid s =>
s -> [t] -> s -> s -> (t -> s) -> Bool -> [Fuzzy t s]
filter s
pattern [t]
ts s
pre s
post t -> s
extract Bool
caseSen =
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (forall a. a -> Down a
Down forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t s. TextualMonoid s => Fuzzy t s -> Int
score)
(forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\t
t -> forall s t.
TextualMonoid s =>
s -> t -> s -> s -> (t -> s) -> Bool -> Maybe (Fuzzy t s)
match s
pattern t
t s
pre s
post t -> s
extract Bool
caseSen) [t]
ts)
{-# INLINABLE simpleFilter #-}
simpleFilter :: (T.TextualMonoid s)
=> s
-> [s]
-> [s]
simpleFilter :: forall s. TextualMonoid s => s -> [s] -> [s]
simpleFilter s
pattern [s]
xs =
forall a b. (a -> b) -> [a] -> [b]
map forall t s. TextualMonoid s => Fuzzy t s -> t
original forall a b. (a -> b) -> a -> b
$ forall s t.
TextualMonoid s =>
s -> [t] -> s -> s -> (t -> s) -> Bool -> [Fuzzy t s]
filter s
pattern [s]
xs forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. a -> a
id Bool
False
test :: (T.TextualMonoid s)
=> s -> s -> Bool
test :: forall s. TextualMonoid s => s -> s -> Bool
test s
p s
s = forall a. Maybe a -> Bool
isJust (forall s t.
TextualMonoid s =>
s -> t -> s -> s -> (t -> s) -> Bool -> Maybe (Fuzzy t s)
match s
p s
s forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. a -> a
id Bool
False)