[API FIX] search docs ok
[gargantext.git] / src / Gargantext / Viz / Phylo / PhyloMaker.hs
index a8c7e62d9c7824b68313af401aed4618480db3a3..988a490959762000fe1415bd25d8131616225371 100644 (file)
@@ -8,16 +8,11 @@ Stability   : experimental
 Portability : POSIX
 -}
 
-{-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE FlexibleContexts  #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE MultiParamTypeClasses #-}
 
 module Gargantext.Viz.Phylo.PhyloMaker where
 
-import Data.List (concat, nub, partition, sort, (++), group, intersect, null, sortOn, groupBy)
-import Data.Map (Map, fromListWith, keys, unionWith, fromList, empty, toList, elems, (!), restrictKeys, foldlWithKey)
-import Data.Set (size)
+import Data.List (concat, nub, partition, sort, (++), group, intersect, null, sortOn, groupBy, tail)
+import Data.Map (Map, fromListWith, keys, unionWith, fromList, empty, toList, elems, (!), restrictKeys, foldlWithKey, insert)
 import Data.Vector (Vector)
 
 import Gargantext.Prelude
@@ -27,6 +22,8 @@ import Gargantext.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, consta
 import Gargantext.Viz.Phylo.SynchronicClustering (synchronicClustering)
 import Gargantext.Text.Context (TermList)
 import Gargantext.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
+import Gargantext.Viz.Graph.MaxClique (getMaxCliques)
+import Gargantext.Viz.Graph.Distances (Distance(Conditional))
 
 import Control.DeepSeq (NFData)
 import Control.Parallel.Strategies (parList, rdeepseq, using)
@@ -91,7 +88,7 @@ toGroupsProxi lvl phylo =
    in phylo & phylo_groupsProxi .~ ((traceGroupsProxi . fromList) groupsProxi) 
 
 
-appendGroups :: (a -> PhyloPeriodId -> Level -> Int -> Vector Ngrams -> [Cooc] -> PhyloGroup) -> Level -> Map (Date,Date) [a] -> Phylo -> Phylo
+appendGroups :: (a -> PhyloPeriodId -> Level -> Int -> [Cooc] -> PhyloGroup) -> Level -> Map (Date,Date) [a] -> Phylo -> Phylo
 appendGroups f lvl m phylo =  trace ("\n" <> "-- | Append " <> show (length $ concat $ elems m) <> " groups to Level " <> show (lvl) <> "\n")
     $ over ( phylo_periods
            .  traverse
@@ -104,7 +101,7 @@ appendGroups f lvl m phylo =  trace ("\n" <> "-- | Append " <> show (length $ co
                             in  phyloLvl 
                               & phylo_levelGroups .~ (fromList $ foldl (\groups obj ->
                                     groups ++ [ (((pId,lvl),length groups)
-                                              , f obj pId lvl (length groups) (getRoots phylo) 
+                                              , f obj pId lvl (length groups)
                                                   (elems $ restrictKeys (phylo ^. phylo_timeCooc) $ periodsToYears [pId]))
                                               ] ) [] phyloCUnit)
                          else 
@@ -112,14 +109,12 @@ appendGroups f lvl m phylo =  trace ("\n" <> "-- | Append " <> show (length $ co
            phylo  
 
 
-cliqueToGroup :: PhyloClique -> PhyloPeriodId -> Level ->  Int -> Vector Ngrams -> [Cooc] -> PhyloGroup
-cliqueToGroup fis pId lvl idx fdt coocs =
-    let ngrams = ngramsToIdx (Set.toList $ fis ^. phyloClique_nodes) fdt
-    in  PhyloGroup pId lvl idx ""
+cliqueToGroup :: PhyloClique -> PhyloPeriodId -> Level ->  Int -> [Cooc] -> PhyloGroup
+cliqueToGroup fis pId lvl idx coocs = PhyloGroup pId lvl idx ""
                    (fis ^. phyloClique_support)
-                   ngrams
-                   (ngramsToCooc ngrams coocs)
-                   (1,[0]) -- branchid (lvl,[path in the branching tree])
+                   (fis ^. phyloClique_nodes)
+                   (ngramsToCooc (fis ^. phyloClique_nodes) coocs)
+                   (1,[0]) -- branchid (lvl,[path in the branching tree])
                    (fromList [("breaks",[0]),("seaLevels",[0])])
                    [] [] [] []
 
@@ -137,7 +132,8 @@ toPhylo1 docs phyloBase = case (getSeaElevation phyloBase) of
         phyloClique =  toPhyloClique phyloBase docs'
         --------------------------------------
         docs' :: Map (Date,Date) [Document]
-        docs' =  groupDocsByPeriod' date (getPeriodIds phyloBase) docs
+        docs' =  groupDocsByPeriodRec date (getPeriodIds phyloBase) (sortOn date docs) empty
+        -- docs' =  groupDocsByPeriod' date (getPeriodIds phyloBase) docs
         --------------------------------------
 
 
@@ -146,69 +142,82 @@ toPhylo1 docs phyloBase = case (getSeaElevation phyloBase) of
 ---------------------------
 
 
--- | To apply a filter with the possibility of keeping some periods non empty (keep : True|False)
+--  To apply a filter with the possibility of keeping some periods non empty (keep : True|False)
 filterClique :: Bool -> Int -> (Int -> [PhyloClique] -> [PhyloClique]) -> Map (Date, Date) [PhyloClique] -> Map (Date, Date) [PhyloClique]
 filterClique keep thr f m = case keep of
   False -> map (\l -> f thr l) m
   True  -> map (\l -> keepFilled (f) thr l) m
 
 
--- | To filter Fis with small Support
+--  To filter Fis with small Support
 filterCliqueBySupport :: Int -> [PhyloClique] -> [PhyloClique]
 filterCliqueBySupport thr l = filter (\clq -> (clq ^. phyloClique_support) >= thr) l
 
 
--- | To filter Fis with small Clique size
+--  To filter Fis with small Clique size
 filterCliqueBySize :: Int -> [PhyloClique] -> [PhyloClique]
-filterCliqueBySize thr l = filter (\clq -> (size $ clq ^. phyloClique_nodes) >= thr) l
+filterCliqueBySize thr l = filter (\clq -> (length $ clq ^. phyloClique_nodes) >= thr) l
 
 
--- | To filter nested Fis
+--  To filter nested Fis
 filterCliqueByNested :: Map (Date, Date) [PhyloClique] -> Map (Date, Date) [PhyloClique]
 filterCliqueByNested m = 
   let clq  = map (\l -> 
-                foldl (\mem f -> if (any (\f' -> isNested (Set.toList $ f' ^. phyloClique_nodes) (Set.toList $ f ^. phyloClique_nodes)) mem)
+                foldl (\mem f -> if (any (\f' -> isNested (f' ^. phyloClique_nodes) (f ^. phyloClique_nodes)) mem)
                                  then mem
                                  else 
-                                    let fMax = filter (\f' -> not $ isNested (Set.toList $ f ^. phyloClique_nodes) (Set.toList $ f' ^. phyloClique_nodes)) mem
+                                    let fMax = filter (\f' -> not $ isNested (f ^. phyloClique_nodes) (f' ^. phyloClique_nodes)) mem
                                     in  fMax ++ [f] ) [] l)
            $ elems m 
       clq' = clq `using` parList rdeepseq
   in  fromList $ zip (keys m) clq' 
 
 
--- | To transform a time map of docs innto a time map of Fis with some filters
+-- | To transform a time map of docs into a time map of Fis with some filters
 toPhyloClique :: Phylo -> Map (Date, Date) [Document] -> Map (Date,Date) [PhyloClique]
 toPhyloClique phylo phyloDocs = case (clique $ getConfig phylo) of 
-    Fis s s' -> -- traceFis "Filtered Fis"
-                filterCliqueByNested 
-                -- $ traceFis "Filtered by clique size"
-                $ filterClique True s' (filterCliqueBySize)
-                -- $ traceFis "Filtered by support"
-                $ filterClique True s (filterCliqueBySupport)
-                -- $ traceFis "Unfiltered Fis" 
-                phyloClique
-    MaxClique _ -> undefined
+    Fis s s'    -> -- traceFis "Filtered Fis"
+                   filterCliqueByNested 
+                 {- \$ traceFis "Filtered by clique size" -}
+                 $ filterClique True s' (filterCliqueBySize)
+                 {- \$ traceFis "Filtered by support" -}
+                 $ filterClique True s (filterCliqueBySupport)
+                 {- \$ traceFis "Unfiltered Fis" -}
+                 phyloClique
+    MaxClique s -> filterClique True s (filterCliqueBySize)
+                 phyloClique
     where
         -------------------------------------- 
         phyloClique :: Map (Date,Date) [PhyloClique]
         phyloClique = case (clique $ getConfig phylo) of 
-          Fis _ _ ->  let fis  = map (\(prd,docs) -> 
-                                  let lst = toList $ fisWithSizePolyMap (Segment 1 20) 1 (map text docs)
-                                   in (prd, map (\f -> PhyloClique (fst f) (snd f) prd) lst))
+          Fis _ _     ->  
+                      let fis  = map (\(prd,docs) -> 
+                                  let lst = toList $ fisWithSizePolyMap (Segment 1 20) 1 (map (\d -> ngramsToIdx (text d) (getRoots phylo)) docs)
+                                   in (prd, map (\f -> PhyloClique (Set.toList $ fst f) (snd f) prd) lst))
                                $ toList phyloDocs
                           fis' = fis `using` parList rdeepseq
                        in fromList fis'
-          MaxClique _ -> undefined
+          MaxClique _ -> 
+                      let mcl  = map (\(prd,docs) -> 
+                                    let cooc = map round
+                                             $ foldl sumCooc empty
+                                             $ map listToMatrix 
+                                             $ map (\d -> ngramsToIdx (text d) (getRoots phylo)) docs
+                                     in (prd, map (\cl -> PhyloClique cl 0 prd) $ getMaxCliques Conditional 0.001 cooc)) 
+                               $ toList phyloDocs
+                          mcl' = mcl `using` parList rdeepseq                               
+                       in fromList mcl' 
         -------------------------------------- 
 
+        -- dev viz graph maxClique getMaxClique
+
 
 --------------------
 -- | Coocurency | --
 --------------------
 
 
--- | To transform the docs into a time map of coocurency matrix 
+--  To transform the docs into a time map of coocurency matrix 
 docsToTimeScaleCooc :: [Document] -> Vector Ngrams -> Map Date Cooc
 docsToTimeScaleCooc docs fdt = 
     let mCooc  = fromListWith sumCooc
@@ -225,7 +234,17 @@ docsToTimeScaleCooc docs fdt =
 -- | to Phylo Base | --
 -----------------------
 
--- | To group a list of Documents by fixed periods
+groupDocsByPeriodRec :: (NFData doc, Ord date, Enum date) => (doc -> date) -> [(date,date)] -> [doc] -> Map (date, date) [doc] -> Map (date, date) [doc]
+groupDocsByPeriodRec f prds docs acc = 
+    if ((null prds) || (null docs))
+      then acc 
+      else 
+        let prd = head' "groupBy" prds
+            docs' = partition (\d -> (f d >= fst prd) && (f d <= snd prd)) docs
+         in groupDocsByPeriodRec f (tail prds) (snd docs') (insert prd (fst docs') acc)
+
+
+--  To group a list of Documents by fixed periods
 groupDocsByPeriod' :: (NFData doc, Ord date, Enum date) => (doc -> date) -> [(date,date)] -> [doc] -> Map (date, date) [doc]
 groupDocsByPeriod' f pds docs = 
   let docs'    = groupBy (\d d' -> f d == f d') $ sortOn f docs
@@ -241,7 +260,7 @@ groupDocsByPeriod' f pds docs =
 
 
 
--- | To group a list of Documents by fixed periods
+--  To group a list of Documents by fixed periods
 groupDocsByPeriod :: (NFData doc, Ord date, Enum date) => (doc -> date) -> [(date,date)] -> [doc] -> Map (date, date) [doc]
 groupDocsByPeriod _ _   [] = panic "[ERR][Viz.Phylo.PhyloMaker] Empty [Documents] can not have any periods"
 groupDocsByPeriod f pds es = 
@@ -269,7 +288,7 @@ docsToTermFreq docs fdt =
    in map (/sumFreqs) freqs
 
 
--- | To count the number of docs by unit of time
+--  To count the number of docs by unit of time
 docsToTimeScaleNb :: [Document] -> Map Date Double
 docsToTimeScaleNb docs = 
     let docs' = fromListWith (+) $ map (\d -> (date d,1)) docs
@@ -283,7 +302,7 @@ initPhyloLevels lvlMax pId =
     fromList $ map (\lvl -> ((pId,lvl),PhyloLevel pId lvl empty)) [1..lvlMax]
 
 
--- | To init the basic elements of a Phylo
+--  To init the basic elements of a Phylo
 toPhyloBase :: [Document] -> TermList -> Config -> Phylo
 toPhyloBase docs lst conf = 
     let foundations  = PhyloFoundations (Vector.fromList $ nub $ concat $ map text docs) lst
@@ -295,5 +314,6 @@ toPhyloBase docs lst conf =
                (docsToTimeScaleNb docs)
                (docsToTermFreq docs (foundations ^. foundations_roots))
                empty
+               empty
                params
                (fromList $ map (\prd -> (prd, PhyloPeriod prd (initPhyloLevels 1 prd))) periods)