Eleve...
[gargantext.git] / src / Gargantext / Database / Flow.hs
index 3f611ee99d9a1ec9ce921d692538a3ec72738bb8..d75917b9f4ab70a8b310dc26edb8025c65d2e292 100644 (file)
@@ -7,310 +7,389 @@ Maintainer  : team@gargantext.org
 Stability   : experimental
 Portability : POSIX
 
+
+-- TODO-ACCESS:
+--   check userId       CanFillUserCorpus   userCorpusId
+--   check masterUserId CanFillMasterCorpus masterCorpusId
+
+-- TODO-ACCESS: check uId CanInsertDoc pId && checkDocType nodeType
+-- TODO-EVENTS: InsertedNodes
+
+
 -}
 
+{-# LANGUAGE ConstraintKinds   #-}
 {-# LANGUAGE DeriveGeneric     #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RankNTypes        #-}
+{-# LANGUAGE FlexibleContexts  #-}
 
 module Gargantext.Database.Flow -- (flowDatabase, ngrams2list)
     where
 
-import GHC.Show (Show)
---import Control.Lens (view)
-import System.FilePath (FilePath)
+--import Debug.Trace (trace)
+import Control.Lens ((^.), view, Lens', _Just)
+import Control.Monad (mapM_)
+import Control.Monad.IO.Class (liftIO)
+import Data.List (concat)
+import Data.Map (Map, lookup, toList)
 import Data.Maybe (Maybe(..), catMaybes)
-import Data.Text (Text, splitOn)
-import Data.Map (Map, lookup)
-import Data.Tuple.Extra (both, second)
-import qualified Data.Map as DM
-import Gargantext.Core.Types (NodePoly(..), ListType(..), listTypeId)
-import Gargantext.Database.Bashql (runCmd') -- , del)
-import Gargantext.Database.Config (userMaster, userArbitrary, corpusMasterName)
-import Gargantext.Database.Schema.Ngrams (insertNgrams, Ngrams(..), NgramsT(..), NgramsIndexed(..), indexNgramsT,  NgramsType(..), text2ngrams)
-import Gargantext.Database.Schema.Node (mkRoot, mkCorpus, mkList, mkGraph, mkDashboard, mkAnnuaire, getCorporaWithParentId')
-import Gargantext.Database.Root (getRootCmd)
-import Gargantext.Database.Types.Node (NodeType(..), NodeId)
-import Gargantext.Database.Node.Document.Add    (add)
-import Gargantext.Database.Node.Document.Insert (insertDocuments, ReturnId(..), addUniqIdsDoc, addUniqIdsContact, ToDbData(..))
-import Gargantext.Database.Schema.NodeNgram (NodeNgramPoly(..), insertNodeNgrams)
-import Gargantext.Database.Schema.NodeNgramsNgrams (NodeNgramsNgramsPoly(..), insertNodeNgramsNgramsNew)
-import Gargantext.Database.Types.Node (HyperdataDocument(..))
-import Gargantext.Database.Utils (Cmd(..))
---import Gargantext.Database.Node.Contact (HyperdataContact(..))
-import Gargantext.Database.Schema.User (getUser, UserLight(..))
+import Data.Monoid
+import Data.Text (Text, splitOn, intercalate)
+import GHC.Show (Show)
+import Gargantext.API.Ngrams (HasRepoVar)
+import Gargantext.API.Ngrams (NgramsElement(..), putListNgrams, RepoCmdM)
+import Gargantext.Core (Lang(..))
+import Gargantext.Core.Types (NodePoly(..), Terms(..))
 import Gargantext.Core.Types.Individu (Username)
+import Gargantext.Core.Types.Main
+import Gargantext.Database.Config (userMaster, corpusMasterName)
+import Gargantext.Database.Flow.Utils (insertDocNgrams)
+import Gargantext.Database.Node.Contact -- (HyperdataContact(..), ContactWho(..))
+import Gargantext.Database.Node.Document.Insert -- (insertDocuments, ReturnId(..), addUniqIdsDoc, addUniqIdsContact, ToDbData(..))
+import Gargantext.Database.Root (getRoot)
+import Gargantext.Database.Schema.Ngrams -- (insertNgrams, Ngrams(..), NgramsIndexed(..), indexNgrams,  NgramsType(..), text2ngrams, ngramsTypeId)
+import Gargantext.Database.Schema.Node -- (mkRoot, mkCorpus, getOrMkList, mkGraph, mkDashboard, mkAnnuaire, getCorporaWithParentId, HasNodeError, NodeError(..), nodeError)
+import Gargantext.Database.Schema.User (getUser, UserLight(..))
+import Gargantext.Database.TextSearch (searchInDatabase)
+import Gargantext.Database.Types.Node -- (HyperdataDocument(..), NodeType(..), NodeId, UserId, ListId, CorpusId, RootId, MasterCorpusId, MasterUserId)
+import Gargantext.Database.Utils (Cmd, CmdM)
 import Gargantext.Ext.IMT (toSchoolName)
 import Gargantext.Ext.IMTUser (deserialiseImtUsersFromFile)
 import Gargantext.Prelude
-import Gargantext.Text.Parsers (parseDocs, FileFormat)
-import Gargantext.Core.Types.Main
---import Gargantext.Core.Types
-import Gargantext.Database.Flow.Utils (insertToNodeNgrams)
+import Gargantext.Text.List (buildNgramsLists,StopSize(..))
+import Gargantext.Text.Parsers (parseFile, FileFormat)
+import Gargantext.Text.Terms (TermType(..), tt_lang)
+import Gargantext.Text.Terms (extractTerms)
+import Gargantext.Text.Terms.Mono.Stem.En (stemIt)
+import Servant (ServantErr)
+import System.FilePath (FilePath)
+--import qualified Data.List as List
+import qualified Data.Map  as Map
+import qualified Data.Text as Text
+import qualified Gargantext.Database.Node.Document.Add  as Doc  (add)
+import qualified Gargantext.Text.Parsers.GrandDebat as GD
+
+type FlowCmdM env err m =
+  ( CmdM     env err m
+  , RepoCmdM env err m
+  , HasNodeError err
+  , HasRepoVar env
+  )
+
+type FlowCorpus a = ( AddUniqId a
+                    , UniqId a
+                    , InsertDb a
+                    , ExtractNgramsT a
+                    )
 
-flowCorpus :: FileFormat -> FilePath -> CorpusName -> IO CorpusId
-flowCorpus ff fp cName = do
-  hyperdataDocuments' <- map addUniqIdsDoc <$> parseDocs ff fp
-  params <- flowInsert NodeCorpus hyperdataDocuments' cName
-  flowCorpus' NodeCorpus hyperdataDocuments' params
+------------------------------------------------------------------------
 
+flowAnnuaire :: FlowCmdM env ServantErr m 
+             => Username -> CorpusName -> (TermType Lang) -> FilePath -> m AnnuaireId
+flowAnnuaire u n l filePath = do
+  docs <- liftIO $ (( splitEvery 500 <$> deserialiseImtUsersFromFile filePath) :: IO [[HyperdataContact]])
+  flow (Nothing :: Maybe HyperdataAnnuaire) u n l docs
+
+
+flowCorpusDebat :: FlowCmdM env ServantErr m
+            => Username -> CorpusName
+            -> Limit -> FilePath
+            -> m CorpusId
+flowCorpusDebat u n l fp = do
+  docs <- liftIO ( splitEvery 500
+                 <$> take l
+                 <$> GD.readFile fp
+                 :: IO [[GD.GrandDebatReference ]]
+                 )
+  flowCorpus u n (Multi FR) (map (map toHyperdataDocument) docs)
+
+
+flowCorpusFile :: FlowCmdM env ServantErr m
+           => Username -> CorpusName
+           -> Limit -- Limit the number of docs (for dev purpose)
+           -> TermType Lang -> FileFormat -> FilePath
+           -> m CorpusId
+flowCorpusFile u n l la ff fp = do
+  docs <- liftIO ( splitEvery 500
+                 <$> take l
+                 <$> parseFile ff fp
+                 )
+  flowCorpus u n la (map (map toHyperdataDocument) docs)
+
+-- TODO query with complex query
+flowCorpusSearchInDatabase :: FlowCmdM env err m
+          => Username -> Lang -> Text -> m CorpusId
+flowCorpusSearchInDatabase u la q = do
+  (_masterUserId, _masterRootId, cId) <- getOrMkRootWithCorpus userMaster "" (Nothing :: Maybe HyperdataCorpus)
+  ids <-  map fst <$> searchInDatabase cId (stemIt q)
+  flowCorpusUser la u q (Nothing :: Maybe HyperdataCorpus) ids
+
+
+flowCorpusSearchInDatabase' :: FlowCmdM env ServantErr m
+          => Username -> Lang -> Text -> m CorpusId
+flowCorpusSearchInDatabase' u la q = do
+  (_masterUserId, _masterRootId, cId) <- getOrMkRootWithCorpus userMaster "" (Nothing :: Maybe HyperdataCorpus)
+  ids <-  map fst <$> searchInDatabase cId (stemIt q)
+  flowCorpusUser la u q (Nothing :: Maybe HyperdataCorpus) ids
 
-flowInsert :: NodeType -> [HyperdataDocument] -> CorpusName
-     -> IO ([ReturnId], MasterUserId, MasterCorpusId, UserId, CorpusId)
-flowInsert _nt hyperdataDocuments cName = do
-  let hyperdataDocuments' = map (\h -> ToDbDocument h) hyperdataDocuments
 
-  (masterUserId, _, masterCorpusId) <- subFlowCorpus userMaster corpusMasterName
-  ids  <- runCmd' $ insertDocuments masterUserId masterCorpusId NodeDocument hyperdataDocuments'
-  
-  (userId, _, userCorpusId) <- subFlowCorpus userArbitrary cName
-  _ <- runCmd' $ add userCorpusId (map reId ids)
-  
-  pure (ids, masterUserId, masterCorpusId, userId, userCorpusId)
+------------------------------------------------------------------------
 
+flow :: (FlowCmdM env ServantErr m, FlowCorpus a, MkCorpus c)
+     => Maybe c -> Username -> CorpusName -> TermType Lang -> [[a]] -> m CorpusId
+flow c u cn la docs = do
+  ids <- mapM (insertMasterDocs c la ) docs
+  flowCorpusUser (la ^. tt_lang) u cn c (concat ids)
 
-flowAnnuaire :: FilePath -> IO ()
-flowAnnuaire filePath = do
-  contacts <- deserialiseImtUsersFromFile filePath
-  ps <- flowInsertAnnuaire "Annuaire" $ map (\h-> ToDbContact h) $ map addUniqIdsContact contacts
-  printDebug "length annuaire" ps
+flowCorpus :: (FlowCmdM env ServantErr m, FlowCorpus a)
+     => Username -> CorpusName -> TermType Lang -> [[a]] -> m CorpusId
+flowCorpus = flow (Nothing :: Maybe HyperdataCorpus)
 
 
-flowInsertAnnuaire :: CorpusName -> [ToDbData]
-                    -> IO ([ReturnId], UserId, CorpusId, UserId, CorpusId)
-flowInsertAnnuaire name children = do
+flowCorpusUser :: (FlowCmdM env err m, MkCorpus c)
+               => Lang -> Username -> CorpusName -> Maybe c -> [NodeId] -> m CorpusId
+flowCorpusUser l userName corpusName ctype ids = do
+  -- User Flow
+  (userId, _rootId, userCorpusId) <- getOrMkRootWithCorpus userName corpusName ctype
+  -- TODO: check if present already, ignore
+  _ <- Doc.add userCorpusId ids
 
-  (masterUserId, _, masterCorpusId) <- subFlowCorpus userMaster corpusMasterName
-  ids  <- runCmd' $ insertDocuments masterUserId masterCorpusId NodeContact children
-  
-  (userId, _, userCorpusId) <- subFlowAnnuaire userArbitrary name
-  _ <- runCmd' $ add userCorpusId (map reId ids)
-  
-  printDebug "AnnuaireID" userCorpusId
+  -- User List Flow
+  --{-
+  (_masterUserId, _masterRootId, masterCorpusId) <- getOrMkRootWithCorpus userMaster "" ctype
+  ngs         <- buildNgramsLists l 2 3 (StopSize 3) userCorpusId masterCorpusId
+  userListId  <- flowList userId userCorpusId ngs
+  printDebug "userListId" userListId
+  -- User Graph Flow
+  _ <- mkGraph  userCorpusId userId
+  --}
 
-  pure (ids, masterUserId, masterCorpusId, userId, userCorpusId)
+  -- User Dashboard Flow
+  _ <- mkDashboard userCorpusId userId
 
+  -- Annuaire Flow
+  -- _ <- mkAnnuaire  rootUserId userId
+  pure userCorpusId
 
-flowCorpus' :: NodeType -> [HyperdataDocument]
-            -> ([ReturnId], UserId, CorpusId, UserId, CorpusId)
-            -> IO CorpusId
-flowCorpus' NodeCorpus hyperdataDocuments (ids,masterUserId,masterCorpusId, userId,userCorpusId) = do
---------------------------------------------------
-  -- List Ngrams Flow
-  userListId <- runCmd' $ flowListUser userId userCorpusId
-  printDebug "Working on User ListId : " userListId
-  
-  let documentsWithId = mergeData (toInserted ids) (toInsert hyperdataDocuments)
-  -- printDebug "documentsWithId" documentsWithId
-  let docsWithNgrams  = documentIdWithNgrams extractNgramsT documentsWithId
-  -- printDebug "docsWithNgrams" docsWithNgrams
-  let maps            = mapNodeIdNgrams docsWithNgrams
-  
-  -- printDebug "maps" (maps)
-  indexedNgrams <- runCmd' $ indexNgrams maps
-  -- printDebug "inserted ngrams" indexedNgrams
-  _             <- runCmd' $ insertToNodeNgrams indexedNgrams
+
+insertMasterDocs :: ( FlowCmdM env ServantErr m
+                    , FlowCorpus a
+                    , MkCorpus   c
+                    )
+                 => Maybe c -> TermType Lang -> [a] -> m [DocId]
+insertMasterDocs c lang hs  =  do
+  (masterUserId, _, masterCorpusId) <- getOrMkRootWithCorpus userMaster corpusMasterName c
+
+  -- TODO Type NodeDocumentUnicised
+  let hs' = map addUniqId hs
+  ids <- insertDb masterUserId masterCorpusId hs'
+  let documentsWithId = mergeData (toInserted ids) (Map.fromList $ map viewUniqId' hs')
   
-  listId2    <- runCmd' $ flowList masterUserId masterCorpusId indexedNgrams
-  printDebug "Working on ListId : " listId2
-  --}
---------------------------------------------------
-  _ <- runCmd' $ mkDashboard userCorpusId userId
-  _ <- runCmd' $ mkGraph     userCorpusId userId
+  maps <- mapNodeIdNgrams <$> documentIdWithNgrams (extractNgramsT lang) documentsWithId
+  terms2id <- insertNgrams $ Map.keys maps
+  let indexedNgrams = Map.mapKeys (indexNgrams terms2id) maps
   
-  -- Annuaire Flow
-  -- _ <- runCmd' $ mkAnnuaire  rootUserId userId
-
-  pure userCorpusId
-  -- runCmd' $ del [corpusId2, corpusId]
+  lId <- getOrMkList masterCorpusId masterUserId
+  _   <- insertDocNgrams lId indexedNgrams
+  pure $ map reId ids
 
-flowCorpus' NodeAnnuaire _hyperdataDocuments (_ids,_masterUserId,_masterCorpusId,_userId,_userCorpusId) = undefined
-flowCorpus' _ _ _ = undefined
 
 
 type CorpusName = Text
 
-subFlowCorpus :: Username -> CorpusName -> IO (UserId, RootId, CorpusId)
-subFlowCorpus username cName = do
-  maybeUserId <- runCmd' (getUser username)
+getOrMkRootWithCorpus :: (HasNodeError err, MkCorpus a)
+              => Username -> CorpusName -> Maybe a
+              -> Cmd err (UserId, RootId, CorpusId)
+getOrMkRootWithCorpus username cName c = do
+  maybeUserId <- getUser username
+  userId <- case maybeUserId of
+        Nothing   -> nodeError NoUserFound
+        Just user -> pure $ userLight_id user
 
-  let userId = case maybeUserId of
-        Nothing   -> panic "Error: User does not exist (yet)"
-        -- mk NodeUser gargantua_id "Node Gargantua"
-        Just user -> userLight_id user
-
-  rootId' <- map _node_id <$> runCmd' (getRootCmd username)
+  rootId' <- map _node_id <$> getRoot username
 
   rootId'' <- case rootId' of
-        []  -> runCmd' (mkRoot username userId)
+        []  -> mkRoot username userId
         n   -> case length n >= 2 of
-            True  -> panic "Error: more than 1 userNode / user"
+            True  -> nodeError ManyNodeUsers
             False -> pure rootId'
-  let rootId = maybe (panic "error rootId") identity (head rootId'')
-  --{-
+
+  rootId <- maybe (nodeError NoRootFound) pure (head rootId'')
+
   corpusId'' <- if username == userMaster
                   then do
-                    ns <- runCmd' $ getCorporaWithParentId' rootId
+                    ns <- getCorporaWithParentId rootId
                     pure $ map _node_id ns
                   else
                     pure []
-
---}
+  
   corpusId' <- if corpusId'' /= []
                   then pure corpusId''
-                  else runCmd' $ mkCorpus (Just cName) Nothing rootId userId
+                  else mk (Just cName) c rootId userId
 
-  let corpusId = maybe (panic "error corpusId") identity (head corpusId')
+  corpusId <- maybe (nodeError NoCorpusFound) pure (head corpusId')
 
-  printDebug "(username, userId, rootId, corpusId)"
-              (username, userId, rootId, corpusId)
   pure (userId, rootId, corpusId)
 
 
-subFlowAnnuaire :: Username -> CorpusName -> IO (UserId, RootId, CorpusId)
-subFlowAnnuaire username _cName = do
-  maybeUserId <- runCmd' (getUser username)
-
-  let userId = case maybeUserId of
-        Nothing   -> panic "Error: User does not exist (yet)"
-        -- mk NodeUser gargantua_id "Node Gargantua"
-        Just user -> userLight_id user
+------------------------------------------------------------------------
 
-  rootId' <- map _node_id <$> runCmd' (getRootCmd username)
 
-  rootId'' <- case rootId' of
-        []  -> runCmd' (mkRoot username userId)
-        n   -> case length n >= 2 of
-            True  -> panic "Error: more than 1 userNode / user"
-            False -> pure rootId'
-  let rootId = maybe (panic "error rootId") identity (head rootId'')
+class UniqId a
+  where
+    uniqId :: Lens' a (Maybe HashId)
 
-  corpusId' <- runCmd' $ mkAnnuaire rootId userId
-  
-  let corpusId = maybe (panic "error corpusId") identity (head corpusId')
 
-  printDebug "(username, userId, rootId, corpusId)"
-              (username, userId, rootId, corpusId)
-  pure (userId, rootId, corpusId)
+instance UniqId HyperdataDocument
+  where
+    uniqId = hyperdataDocument_uniqId
 
+instance UniqId HyperdataContact
+  where
+    uniqId = hc_uniqId
 
+viewUniqId' :: UniqId a => a -> (HashId, a)
+viewUniqId' d = maybe err (\h -> (h,d)) (view uniqId d)
+      where
+        err = panic "[ERROR] Database.Flow.toInsert"
 
-------------------------------------------------------------------------
-toInsert :: [HyperdataDocument] -> Map HashId HyperdataDocument
-toInsert = DM.fromList . map (\d -> (maybe err identity (_hyperdataDocument_uniqId d), d))
-  where
-    err = "Database.Flow.toInsert"
 
 toInserted :: [ReturnId] -> Map HashId ReturnId
-toInserted = DM.fromList . map    (\r ->  (reUniqId r, r)    )
+toInserted = Map.fromList . map    (\r ->  (reUniqId r, r)    )
                          . filter (\r -> reInserted r == True)
 
-data DocumentWithId =
-     DocumentWithId { documentId   :: NodeId
-                    , documentData :: HyperdataDocument
-                    } deriving (Show)
+data DocumentWithId a = DocumentWithId
+  { documentId   :: !NodeId
+  , documentData :: !a
+  } deriving (Show)
 
-mergeData :: Map HashId ReturnId -> Map HashId HyperdataDocument -> [DocumentWithId]
-mergeData rs = catMaybes . map toDocumentWithId . DM.toList
+mergeData :: Map HashId ReturnId
+          -> Map HashId a
+          -> [DocumentWithId a]
+mergeData rs = catMaybes . map toDocumentWithId . Map.toList
   where
     toDocumentWithId (hash,hpd) =
       DocumentWithId <$> fmap reId (lookup hash rs)
                      <*> Just hpd
 
 ------------------------------------------------------------------------
+data DocumentIdWithNgrams a = DocumentIdWithNgrams
+  { documentWithId  :: !(DocumentWithId a)
+  , document_ngrams :: !(Map Ngrams (Map NgramsType Int))
+  } deriving (Show)
 
-data DocumentIdWithNgrams =
-     DocumentIdWithNgrams
-     { documentWithId  :: DocumentWithId
-     , document_ngrams :: Map (NgramsT Ngrams) Int
-     } deriving (Show)
-
--- TODO add Terms (Title + Abstract)
--- add f :: Text -> Text
--- newtype Ngrams = Ngrams Text
-extractNgramsT :: HyperdataDocument -> Map (NgramsT Ngrams) Int
-extractNgramsT doc = DM.fromList $  [(NgramsT Sources source, 1)]
-                                 <> [(NgramsT Institutes i' , 1)| i' <- institutes ]
-                                 <> [(NgramsT Authors    a' , 1)| a' <- authors    ]
-  where
-    source    = text2ngrams $ maybe "Nothing" identity $ _hyperdataDocument_source doc
-    institutes = map text2ngrams $ maybe ["Nothing"] (map toSchoolName . (splitOn ", "))  $ _hyperdataDocument_institutes doc
-    authors    = map text2ngrams $ maybe ["Nothing"] (splitOn ", ") $ _hyperdataDocument_authors doc
-    -- TODO group terms
-
+-- TODO extractNgrams according to Type of Data
 
-
-
-documentIdWithNgrams :: (HyperdataDocument -> Map (NgramsT Ngrams) Int)
-                     -> [DocumentWithId]   -> [DocumentIdWithNgrams]
-documentIdWithNgrams f = map (\d -> DocumentIdWithNgrams d ((f . documentData) d))
-
--- | TODO check optimization
-mapNodeIdNgrams :: [DocumentIdWithNgrams] -> Map (NgramsT Ngrams) (Map NodeId Int)
-mapNodeIdNgrams ds = DM.map (DM.fromListWith (+)) $ DM.fromListWith (<>) xs
+class ExtractNgramsT h
   where
-    xs  = [(ng, [(nId, i)]) | (nId, n2i') <- n2i ds, (ng, i) <- DM.toList n2i']
-    n2i = map (\d -> ((documentId . documentWithId) d, document_ngrams d))
+    extractNgramsT :: TermType Lang -> h -> Cmd err (Map Ngrams (Map NgramsType Int))
 
-indexNgrams :: Map (NgramsT Ngrams       ) (Map NodeId Int)
-       -> Cmd (Map (NgramsT NgramsIndexed) (Map NodeId Int))
-indexNgrams ng2nId = do
-  terms2id <- insertNgrams (map _ngramsT $ DM.keys ng2nId)
-  pure $ DM.mapKeys (indexNgramsT terms2id) ng2nId
 
+instance ExtractNgramsT HyperdataContact
+  where
+    extractNgramsT l hc = filterNgramsT 255 <$> extract l hc
+      where
+        extract :: TermType Lang -> HyperdataContact
+                -> Cmd err (Map Ngrams (Map NgramsType Int))
+        extract _l hc' = do
+          let authors = map text2ngrams
+                     $ maybe ["Nothing"] (\a -> [a])
+                     $ view (hc_who . _Just . cw_lastName) hc'
+        
+          pure $ Map.fromList $ [(a', Map.singleton Authors     1) | a' <- authors    ]
 
-------------------------------------------------------------------------
-------------------------------------------------------------------------
-flowList :: UserId -> CorpusId -> Map (NgramsT NgramsIndexed) (Map NodeId Int) -> Cmd ListId
-flowList uId cId ngs = do
-  -- printDebug "ngs:" ngs
-  lId <- maybe (panic "mkList error") identity <$> head <$> mkList cId uId
-  --printDebug "ngs" (DM.keys ngs)
-  -- TODO add stemming equivalence of 2 ngrams
-  let groupEd = groupNgramsBy (\(NgramsT t1 n1) (NgramsT t2 n2) -> if (((==) t1 t2) && ((==) n1 n2)) then (Just (n1,n2)) else Nothing) ngs
-  _ <- insertGroups lId groupEd
-
--- compute Candidate / Map
-  let lists = ngrams2list ngs
-  -- printDebug "lists:" lists
-  
-  is <- insertLists lId lists
-  printDebug "listNgrams inserted :" is
 
-  pure lId
 
-flowListUser :: UserId -> CorpusId -> Cmd [Int]
-flowListUser uId cId = mkList cId uId
 
-------------------------------------------------------------------------
+instance ExtractNgramsT HyperdataDocument
+  where
+    extractNgramsT = extractNgramsT'
 
-groupNgramsBy :: (NgramsT NgramsIndexed -> NgramsT NgramsIndexed -> Maybe (NgramsIndexed, NgramsIndexed))
-              -> Map (NgramsT NgramsIndexed) (Map NodeId Int)
-              -> Map NgramsIndexed NgramsIndexed
-groupNgramsBy isEqual cId = DM.fromList $ catMaybes [ isEqual n1 n2 | n1 <- DM.keys cId, n2 <- DM.keys cId]
+extractNgramsT' :: TermType Lang -> HyperdataDocument
+               -> Cmd err (Map Ngrams (Map NgramsType Int))
+extractNgramsT' lang hd = filterNgramsT 255 <$> extractNgramsT'' lang hd
+  where
+    extractNgramsT'' :: TermType Lang -> HyperdataDocument
+                   -> Cmd err (Map Ngrams (Map NgramsType Int))
+    extractNgramsT'' lang' doc = do
+      let source    = text2ngrams
+                    $ maybe "Nothing" identity
+                    $ _hyperdataDocument_source doc
+
+          institutes = map text2ngrams
+                     $ maybe ["Nothing"] (map toSchoolName . (splitOn ", "))
+                     $ _hyperdataDocument_institutes doc
+
+          authors    = map text2ngrams
+                     $ maybe ["Nothing"] (splitOn ", ")
+                     $ _hyperdataDocument_authors doc
+
+          leText = catMaybes [ _hyperdataDocument_title    doc
+                             , _hyperdataDocument_abstract doc
+                             ]
+
+      terms' <- map text2ngrams
+             <$> map (intercalate " " . _terms_label)
+             <$> concat
+             <$> liftIO (extractTerms lang' leText)
+
+      pure $ Map.fromList $  [(source, Map.singleton Sources 1)]
+                         <> [(i', Map.singleton Institutes  1) | i' <- institutes ]
+                         <> [(a', Map.singleton Authors     1) | a' <- authors    ]
+                         <> [(t', Map.singleton NgramsTerms 1) | t' <- terms'     ]
+
+
+filterNgramsT :: Int -> Map Ngrams (Map NgramsType Int)
+                     -> Map Ngrams (Map NgramsType Int)
+filterNgramsT s ms = Map.fromList $ map (\a -> filter' s a) $ Map.toList ms
+  where
+    filter' s' (ng@(Ngrams t n),y) = case (Text.length t) < s' of
+          True  -> (ng,y)
+          False -> (Ngrams (Text.take s' t) n , y)
 
 
+documentIdWithNgrams :: HasNodeError err
+                     => (a
+                     -> Cmd err (Map Ngrams (Map NgramsType Int)))
+                     -> [DocumentWithId a]
+                     -> Cmd err [DocumentIdWithNgrams a]
+documentIdWithNgrams f = mapM toDocumentIdWithNgrams
+  where
+    toDocumentIdWithNgrams d = do
+      e <- f $ documentData d
+      pure $ DocumentIdWithNgrams d e
 
--- TODO check: do not insert duplicates
-insertGroups :: ListId -> Map NgramsIndexed NgramsIndexed -> Cmd Int
-insertGroups lId ngrs =
-  insertNodeNgramsNgramsNew [ NodeNgramsNgrams lId ng1 ng2 (Just 1)
-                              | (ng1, ng2) <- map (both _ngramsId) $ DM.toList ngrs
-                              , ng1 /= ng2
-                            ]
 
-------------------------------------------------------------------------
--- TODO: verify NgramsT lost here
-ngrams2list :: Map (NgramsT NgramsIndexed) (Map NodeId Int) -> [(ListType,NgramsIndexed)]
-ngrams2list = zip (repeat CandidateList) . map (\(NgramsT _lost_t ng) -> ng) . DM.keys
 
--- | TODO: weight of the list could be a probability
-insertLists :: ListId -> [(ListType,NgramsIndexed)] -> Cmd Int
-insertLists lId lngs =
-  insertNodeNgrams [ NodeNgram Nothing lId ngr (fromIntegral $ listTypeId l) (listTypeId l)
-                     | (l,ngr) <- map (second _ngramsId) lngs
-                   ]
+-- FLOW LIST
+-- | TODO check optimization
+mapNodeIdNgrams :: [DocumentIdWithNgrams a]
+                -> Map Ngrams (Map NgramsType (Map NodeId Int))
+mapNodeIdNgrams = Map.unionsWith (Map.unionWith (Map.unionWith (+))) . fmap f
+  where
+    f :: DocumentIdWithNgrams a
+      -> Map Ngrams (Map NgramsType (Map NodeId Int))
+    f d = fmap (fmap (Map.singleton nId)) $ document_ngrams d
+      where
+        nId = documentId $ documentWithId d
 
 ------------------------------------------------------------------------
-------------------------------------------------------------------------
+listInsert :: FlowCmdM env err m
+             => ListId -> Map NgramsType [NgramsElement]
+             -> m ()
+listInsert lId ngs = mapM_ (\(typeList, ngElmts)
+                             -> putListNgrams lId typeList ngElmts
+                             ) $ toList ngs
+
+flowList :: FlowCmdM env err m => UserId -> CorpusId
+         -> Map NgramsType [NgramsElement]
+         -> m ListId
+flowList uId cId ngs = do
+  lId <- getOrMkList cId uId
+  printDebug "listId flowList" lId
+  listInsert lId ngs
+  --trace (show $ List.filter (\n -> _ne_ngrams n == "versatile") $ List.concat $ Map.elems ngs) $ listInsert lId ngs
+  pure lId