Commit 109d8b9e authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DEBUG] Phylo print debug

parent 67db03cc
Pipeline #2553 failed with stage
in 31 minutes and 25 seconds
......@@ -95,7 +95,6 @@ flowPhyloAPI config cId = do
corpusIdtoDocuments :: TimeUnit -> CorpusId -> GargNoServer (TermList, [Document])
corpusIdtoDocuments timeUnit corpusId = do
docs <- selectDocNodes corpusId
lId <- defaultList corpusId
repo <- getRepo' [lId]
......@@ -104,15 +103,16 @@ corpusIdtoDocuments timeUnit corpusId = do
termList <- getTermList lId MapTerm NgramsTerms
case termList of
Nothing -> panic "[G.C.V.Phylo.API] no termList found"
Just termList' -> pure (termList', docs')
where
docs' = catMaybes
let docs'= catMaybes
$ List.map (\doc
-> context2phyloDocument timeUnit doc (ngs_terms, ngs_sources)
) docs
printDebug "corpusIdtoDocuments" (Prelude.map date docs')
case termList of
Nothing -> panic "[G.C.V.Phylo.API] no termList found"
Just termList' -> pure (termList', docs')
context2phyloDocument :: TimeUnit
-> Context HyperdataDocument
......
......@@ -8,10 +8,8 @@ Stability : experimental
Portability : POSIX
-}
module Gargantext.Core.Viz.Phylo.PhyloMaker where
import Control.DeepSeq (NFData)
import Control.Lens hiding (Level)
import Control.Parallel.Strategies (parList, rdeepseq, using)
......
......@@ -140,6 +140,7 @@ periodsToYears periods = (Set.fromList . sort . concat)
findBounds :: [Date] -> (Date,Date)
findBounds [] = panic "[G.C.V.P.PhyloTools] nod Dates for find bounds"
findBounds dates =
let dates' = sort dates
in (head' "findBounds" dates', last' "findBounds" dates')
......
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