Commit 78a8feda authored by Alexandre Delanoë's avatar Alexandre Delanoë

[COSMETICS] removing trace.

parent d87c0b12
......@@ -63,4 +63,3 @@ deriveJSON (unPrefix "metrics_") ''Metrics
deriveJSON (unPrefix "m_") ''Metric
......@@ -402,7 +402,8 @@ getMetrics cId maybeListId maybeTabType maybeLimit = do
let ngramsType = ngramsTypeFromTabType maybeTabType
ngs' <- mapTermListRoot [lId] ngramsType
let ngs = Map.unions $ map (\t -> filterListWithRoot t ngs') [GraphTerm, StopTerm, CandidateTerm]
let ngs = Map.unions $ map (\t -> filterListWithRoot t ngs')
[GraphTerm, StopTerm, CandidateTerm]
myCooc <- Map.filter (>1) <$> getCoocByNgrams
<$> groupNodesByNgrams ngs
......
......@@ -19,7 +19,6 @@ module Gargantext.Text.Metrics
where
--import Data.Array.Accelerate ((:.)(..), Z(..))
import Debug.Trace (trace)
--import Math.KMeans (kmeans, euclidSq, elements)
import Data.Map (Map)
import Data.List.Extra (sortOn)
......@@ -57,7 +56,7 @@ scored m = zipWith (\(_,t) (inc,spe) -> Scored t inc spe) (M.toList fi) scores
where
(ti, fi) = createIndices m
(is, ss) = incExcSpeGen $ cooc2mat ti m
scores = trace (show is) $ DAA.toList
scores = DAA.toList
$ DAA.run
$ DAA.zip (DAA.use is) (DAA.use ss)
......
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