module Text.Fuzzy.Parallel
( filter,
simpleFilter,
Fuzzy(..),
match
) where
import Control.Monad.ST (runST)
import Control.Parallel.Strategies (Eval, Strategy, evalTraversable,
parTraversable, rseq, using)
import Data.Monoid.Textual (TextualMonoid)
import Data.Vector (Vector, (!))
import qualified Data.Vector as V
import Data.Bifunctor (second)
import Data.Maybe (fromJust)
import Prelude hiding (filter)
import Text.Fuzzy (Fuzzy (..), match)
filter :: (TextualMonoid s)
=> Int
-> Int
-> s
-> [t]
-> s
-> s
-> (t -> s)
-> Bool
-> [Fuzzy t s]
filter :: Int -> Int -> s -> [t] -> s -> s -> (t -> s) -> Bool -> [Fuzzy t s]
filter Int
chunkSize Int
maxRes s
pattern [t]
ts s
pre s
post t -> s
extract Bool
caseSen = (forall s. ST s [Fuzzy t s]) -> [Fuzzy t s]
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s [Fuzzy t s]) -> [Fuzzy t s])
-> (forall s. ST s [Fuzzy t s]) -> [Fuzzy t s]
forall a b. (a -> b) -> a -> b
$ do
let v :: Vector (Fuzzy t s)
v = (Maybe (Fuzzy t s) -> Maybe (Fuzzy t s))
-> Vector (Maybe (Fuzzy t s)) -> Vector (Fuzzy t s)
forall a b. (a -> Maybe b) -> Vector a -> Vector b
V.mapMaybe Maybe (Fuzzy t s) -> Maybe (Fuzzy t s)
forall a. a -> a
id
((t -> Maybe (Fuzzy t s)) -> Vector t -> Vector (Maybe (Fuzzy t s))
forall a b. (a -> b) -> Vector a -> Vector b
V.map (\t
t -> s -> t -> s -> s -> (t -> s) -> Bool -> Maybe (Fuzzy t s)
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] -> Vector t
forall a. [a] -> Vector a
V.fromList [t]
ts)
Vector (Maybe (Fuzzy t s))
-> Strategy (Vector (Maybe (Fuzzy t s)))
-> Vector (Maybe (Fuzzy t s))
forall a. a -> Strategy a -> a
`using`
Int
-> Strategy (Maybe (Fuzzy t s))
-> Strategy (Vector (Maybe (Fuzzy t s)))
forall a. Int -> Strategy a -> Vector a -> Eval (Vector a)
parVectorChunk Int
chunkSize (Strategy (Fuzzy t s) -> Strategy (Maybe (Fuzzy t s))
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
evalTraversable Strategy (Fuzzy t s)
forall s t. TextualMonoid s => Fuzzy t s -> Eval (Fuzzy t s)
forceScore))
perfectScore :: Int
perfectScore = Fuzzy s s -> Int
forall t s. TextualMonoid s => Fuzzy t s -> Int
score (Fuzzy s s -> Int) -> Fuzzy s s -> Int
forall a b. (a -> b) -> a -> b
$ Maybe (Fuzzy s s) -> Fuzzy s s
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Fuzzy s s) -> Fuzzy s s) -> Maybe (Fuzzy s s) -> Fuzzy s s
forall a b. (a -> b) -> a -> b
$ s -> s -> s -> s -> (s -> s) -> Bool -> Maybe (Fuzzy s s)
forall s t.
TextualMonoid s =>
s -> t -> s -> s -> (t -> s) -> Bool -> Maybe (Fuzzy t s)
match s
pattern s
pattern s
"" s
"" s -> s
forall a. a -> a
id Bool
False
[Fuzzy t s] -> ST s [Fuzzy t s]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Fuzzy t s] -> ST s [Fuzzy t s])
-> [Fuzzy t s] -> ST s [Fuzzy t s]
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector (Fuzzy t s) -> [Fuzzy t s]
forall s t.
TextualMonoid s =>
Int -> Int -> Vector (Fuzzy t s) -> [Fuzzy t s]
partialSortByAscScore Int
maxRes Int
perfectScore Vector (Fuzzy t s)
v
{-# INLINABLE simpleFilter #-}
simpleFilter :: (TextualMonoid s)
=> Int
-> Int
-> s
-> [s]
-> [s]
simpleFilter :: Int -> Int -> s -> [s] -> [s]
simpleFilter Int
chunk Int
maxRes s
pattern [s]
xs =
(Fuzzy s s -> s) -> [Fuzzy s s] -> [s]
forall a b. (a -> b) -> [a] -> [b]
map Fuzzy s s -> s
forall t s. TextualMonoid s => Fuzzy t s -> t
original ([Fuzzy s s] -> [s]) -> [Fuzzy s s] -> [s]
forall a b. (a -> b) -> a -> b
$ Int -> Int -> s -> [s] -> s -> s -> (s -> s) -> Bool -> [Fuzzy s s]
forall s t.
TextualMonoid s =>
Int -> Int -> s -> [t] -> s -> s -> (t -> s) -> Bool -> [Fuzzy t s]
filter Int
chunk Int
maxRes s
pattern [s]
xs s
forall a. Monoid a => a
mempty s
forall a. Monoid a => a
mempty s -> s
forall a. a -> a
id Bool
False
forceScore :: TextualMonoid s => Fuzzy t s -> Eval(Fuzzy t s)
forceScore :: Fuzzy t s -> Eval (Fuzzy t s)
forceScore it :: Fuzzy t s
it@Fuzzy{Int
score :: Int
score :: forall t s. TextualMonoid s => Fuzzy t s -> Int
score} = do
Int
score' <- Strategy Int
forall a. Strategy a
rseq Int
score
return Fuzzy t s
it{score :: Int
score = Int
score'}
parVectorChunk :: Int -> Strategy a -> Vector a -> Eval (Vector a)
parVectorChunk :: Int -> Strategy a -> Vector a -> Eval (Vector a)
parVectorChunk Int
chunkSize Strategy a
st Vector a
v =
[Vector a] -> Vector a
forall a. [Vector a] -> Vector a
V.concat ([Vector a] -> Vector a) -> Eval [Vector a] -> Eval (Vector a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Vector a -> Eval (Vector a)) -> Strategy [Vector a]
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
parTraversable (Strategy a -> Vector a -> Eval (Vector a)
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
evalTraversable Strategy a
st) (Int -> Vector a -> [Vector a]
forall a. Int -> Vector a -> [Vector a]
chunkVector Int
chunkSize Vector a
v)
chunkVector :: Int -> Vector a -> [Vector a]
chunkVector :: Int -> Vector a -> [Vector a]
chunkVector Int
chunkSize Vector a
v = do
let indices :: [(Int, Int)]
indices = Int -> (Int, Int) -> [(Int, Int)]
chunkIndices Int
chunkSize (Int
0,Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
v)
[Int -> Int -> Vector a -> Vector a
forall a. Int -> Int -> Vector a -> Vector a
V.slice Int
l (Int
hInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l) Vector a
v | (Int
l,Int
h) <- [(Int, Int)]
indices]
chunkIndices :: Int -> (Int,Int) -> [(Int,Int)]
chunkIndices :: Int -> (Int, Int) -> [(Int, Int)]
chunkIndices Int
chunkSize (Int
from,Int
to) =
((Int, Int) -> (Int, Int)) -> [(Int, Int)] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map ((Int -> Int) -> (Int, Int) -> (Int, Int)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second Int -> Int
forall a. Enum a => a -> a
pred) ([(Int, Int)] -> [(Int, Int)]) -> [(Int, Int)] -> [(Int, Int)]
forall a b. (a -> b) -> a -> b
$
[Int] -> [(Int, Int)]
forall a. [a] -> [(a, a)]
pairwise ([Int] -> [(Int, Int)]) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> a -> b
$
[Int
from, Int
fromInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
chunkSize .. Int
toInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [Int
to]
pairwise :: [a] -> [(a,a)]
pairwise :: [a] -> [(a, a)]
pairwise [] = []
pairwise [a
_] = []
pairwise (a
x:a
y:[a]
xs) = (a
x,a
y) (a, a) -> [(a, a)] -> [(a, a)]
forall a. a -> [a] -> [a]
: [a] -> [(a, a)]
forall a. [a] -> [(a, a)]
pairwise (a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
xs)
partialSortByAscScore :: TextualMonoid s
=> Int
-> Int
-> Vector (Fuzzy t s)
-> [Fuzzy t s]
partialSortByAscScore :: Int -> Int -> Vector (Fuzzy t s) -> [Fuzzy t s]
partialSortByAscScore Int
wantedCount Int
perfectScore Vector (Fuzzy t s)
v = Int -> SortState Any -> [Fuzzy t s] -> [Fuzzy t s]
forall a. Int -> SortState a -> [Fuzzy t s] -> [Fuzzy t s]
loop Int
0 (Int -> Int -> Int -> SortState Any
forall a. Int -> Int -> Int -> SortState a
SortState Int
forall a. Bounded a => a
minBound Int
perfectScore Int
0) [] where
l :: Int
l = Vector (Fuzzy t s) -> Int
forall a. Vector a -> Int
V.length Vector (Fuzzy t s)
v
loop :: Int -> SortState a -> [Fuzzy t s] -> [Fuzzy t s]
loop Int
index st :: SortState a
st@SortState{Int
foundCount :: forall a. SortState a -> Int
scoreWanted :: forall a. SortState a -> Int
bestScoreSeen :: forall a. SortState a -> Int
foundCount :: Int
scoreWanted :: Int
bestScoreSeen :: Int
..} [Fuzzy t s]
acc
| Int
foundCount Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
wantedCount = [Fuzzy t s] -> [Fuzzy t s]
forall a. [a] -> [a]
reverse [Fuzzy t s]
acc
| Int
index Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
l
= if Int
bestScoreSeen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
scoreWanted
then Int -> SortState a -> [Fuzzy t s] -> [Fuzzy t s]
loop Int
0 SortState a
st{scoreWanted :: Int
scoreWanted = Int
bestScoreSeen, bestScoreSeen :: Int
bestScoreSeen = Int
forall a. Bounded a => a
minBound} [Fuzzy t s]
acc
else [Fuzzy t s] -> [Fuzzy t s]
forall a. [a] -> [a]
reverse [Fuzzy t s]
acc
| Bool
otherwise =
case Vector (Fuzzy t s)
vVector (Fuzzy t s) -> Int -> Fuzzy t s
forall a. Vector a -> Int -> a
!Int
index of
Fuzzy t s
x | Fuzzy t s -> Int
forall t s. TextualMonoid s => Fuzzy t s -> Int
score Fuzzy t s
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
scoreWanted
-> Int -> SortState a -> [Fuzzy t s] -> [Fuzzy t s]
loop (Int
indexInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) SortState a
st{foundCount :: Int
foundCount = Int
foundCountInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1} (Fuzzy t s
xFuzzy t s -> [Fuzzy t s] -> [Fuzzy t s]
forall a. a -> [a] -> [a]
:[Fuzzy t s]
acc)
| Fuzzy t s -> Int
forall t s. TextualMonoid s => Fuzzy t s -> Int
score Fuzzy t s
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
scoreWanted Bool -> Bool -> Bool
&& Fuzzy t s -> Int
forall t s. TextualMonoid s => Fuzzy t s -> Int
score Fuzzy t s
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
bestScoreSeen
-> Int -> SortState a -> [Fuzzy t s] -> [Fuzzy t s]
loop (Int
indexInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) SortState a
st{bestScoreSeen :: Int
bestScoreSeen = Fuzzy t s -> Int
forall t s. TextualMonoid s => Fuzzy t s -> Int
score Fuzzy t s
x} [Fuzzy t s]
acc
| Bool
otherwise
-> Int -> SortState a -> [Fuzzy t s] -> [Fuzzy t s]
loop (Int
indexInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) SortState a
st [Fuzzy t s]
acc
data SortState a = SortState
{ SortState a -> Int
bestScoreSeen :: !Int
, SortState a -> Int
scoreWanted :: !Int
, SortState a -> Int
foundCount :: !Int
}
deriving Int -> SortState a -> ShowS
[SortState a] -> ShowS
SortState a -> String
(Int -> SortState a -> ShowS)
-> (SortState a -> String)
-> ([SortState a] -> ShowS)
-> Show (SortState a)
forall a. Int -> SortState a -> ShowS
forall a. [SortState a] -> ShowS
forall a. SortState a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortState a] -> ShowS
$cshowList :: forall a. [SortState a] -> ShowS
show :: SortState a -> String
$cshow :: forall a. SortState a -> String
showsPrec :: Int -> SortState a -> ShowS
$cshowsPrec :: forall a. Int -> SortState a -> ShowS
Show