ElEve..

parent 910bdf96
...@@ -41,7 +41,7 @@ Notes for current implementation: ...@@ -41,7 +41,7 @@ Notes for current implementation:
module Gargantext.Text.Eleve where module Gargantext.Text.Eleve where
import Debug.Trace (trace) -- import Debug.Trace (trace)
-- import Debug.SimpleReflect -- import Debug.SimpleReflect
import Data.Functor.Reverse import Data.Functor.Reverse
...@@ -234,9 +234,6 @@ class IsTrie trie where ...@@ -234,9 +234,6 @@ class IsTrie trie where
nodeEntropy :: Entropy e => Getting e i e -> trie k i -> e nodeEntropy :: Entropy e => Getting e i e -> trie k i -> e
nodeChild :: Ord k => k -> trie k e -> trie k e nodeChild :: Ord k => k -> trie k e -> trie k e
findTrie :: Ord k => [k] -> trie k e -> trie k e findTrie :: Ord k => [k] -> trie k e -> trie k e
normalizeEntropy :: Entropy e
=> Getting e i e -> ModEntropy i o e
-> trie k i -> trie k o
-- UNUSED -- UNUSED
--nodeAutonomy :: (Ord k, Entropy e) => Getting e i e -> trie k i -> [k] -> e --nodeAutonomy :: (Ord k, Entropy e) => Getting e i e -> trie k i -> [k] -> e
...@@ -253,7 +250,10 @@ instance IsTrie Trie where ...@@ -253,7 +250,10 @@ instance IsTrie Trie where
findTrie ks t = L.foldl (flip nodeChild) t ks findTrie ks t = L.foldl (flip nodeChild) t ks
normalizeEntropy inE modE t = trace (show level) $ go (modE identity) level t normalizeEntropy :: Entropy e
=> Getting e i e -> ModEntropy i o e
-> Trie k i -> Trie k o
normalizeEntropy inE modE t = go (modE identity) level t
where where
level = (entropyLevels inE t) level = (entropyLevels inE t)
go _ [] _ = panic "normalizeEntropy' empty levels" go _ [] _ = panic "normalizeEntropy' empty levels"
...@@ -323,11 +323,6 @@ instance IsTrie Tries where ...@@ -323,11 +323,6 @@ instance IsTrie Tries where
nodeChild k (Tries fwd bwd) = Tries (nodeChild k fwd) (nodeChild k bwd) nodeChild k (Tries fwd bwd) = Tries (nodeChild k fwd) (nodeChild k bwd)
normalizeEntropy inE modE = onTries (normalizeEntropy inE modE)
onTries :: (Trie k i -> Trie k o) -> Tries k i -> Tries k o
onTries f (Tries fwd bwd) = Tries (f fwd) (f bwd)
------------------------------------------------------------------------ ------------------------------------------------------------------------
split :: (IsTrie trie, Entropy e) => Lens' i e -> trie Token i -> [Token] -> [[Token]] split :: (IsTrie trie, Entropy e) => Lens' i e -> trie Token i -> [Token] -> [[Token]]
split _ _ [] = [] split _ _ [] = []
...@@ -440,16 +435,16 @@ testEleve debug n output checks = do ...@@ -440,16 +435,16 @@ testEleve debug n output checks = do
P.putStrLn (show input) P.putStrLn (show input)
-- forM_ pss (P.putStrLn . show) -- forM_ pss (P.putStrLn . show)
P.putStrLn "" P.putStrLn ""
P.putStrLn "Levels:"
forM_ (entropyLevels identity (_fwd t)) $ \level ->
P.putStrLn $ " " <> show level
P.putStrLn ""
P.putStrLn "Forward:" P.putStrLn "Forward:"
printTrie (_fwd t) printTrie (_fwd t)
P.putStrLn "" P.putStrLn ""
P.putStrLn "Backward:" P.putStrLn "Backward:"
printTrie (_bwd t) printTrie (_bwd t)
P.putStrLn "" P.putStrLn ""
P.putStrLn "Levels:"
forM_ (entropyLevels identity t'') $ \level ->
P.putStrLn $ " " <> show level
P.putStrLn ""
P.putStrLn "Normalized:" P.putStrLn "Normalized:"
printTrie nt printTrie nt
P.putStrLn "" P.putStrLn ""
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment