Commit 35ed3bb7 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Social Lists] WIP

parent 3e6c662a
...@@ -25,6 +25,7 @@ import Gargantext.Prelude ...@@ -25,6 +25,7 @@ import Gargantext.Prelude
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Map (Map) import Data.Map (Map)
import Data.Set (Set) import Data.Set (Set)
import Data.Semigroup (Semigroup(..))
import Data.Text (Text) import Data.Text (Text)
import Gargantext.API.Ngrams.Tools -- (getListNgrams) import Gargantext.API.Ngrams.Tools -- (getListNgrams)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
...@@ -34,7 +35,6 @@ import qualified Data.List as List ...@@ -34,7 +35,6 @@ import qualified Data.List as List
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set import qualified Data.Set as Set
flowSocialList :: ( RepoCmdM env err m flowSocialList :: ( RepoCmdM env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
...@@ -44,20 +44,39 @@ flowSocialList :: ( RepoCmdM env err m ...@@ -44,20 +44,39 @@ flowSocialList :: ( RepoCmdM env err m
-> m (Map ListType (Set Text)) -> m (Map ListType (Set Text))
flowSocialList user nt ngrams' = do flowSocialList user nt ngrams' = do
privateLists <- flowSocialListByMode Private user nt ngrams' privateLists <- flowSocialListByMode Private user nt ngrams'
-- printDebug "* privateLists *: \n" privateLists printDebug "* privateLists *: \n" privateLists
-- here preference to privateLists (discutable)
sharedLists <- flowSocialListByMode Shared user nt (termsByList CandidateTerm privateLists) sharedLists <- flowSocialListByMode Shared user nt (termsByList CandidateTerm privateLists)
-- printDebug "* socialLists *: \n" sharedLists printDebug "* sharedLists *: \n" sharedLists
-- TODO publicMapList -- TODO publicMapList
pure $ Map.fromList [ (MapTerm, termsByList MapTerm privateLists let result = unions [ Map.mapKeys (fromMaybe CandidateTerm) privateLists
<> termsByList MapTerm sharedLists , Map.mapKeys (fromMaybe CandidateTerm) sharedLists
)
, (StopTerm, termsByList StopTerm privateLists
<> termsByList StopTerm sharedLists
)
, (CandidateTerm, termsByList CandidateTerm sharedLists)
] ]
printDebug "* socialLists *: results \n" sharedLists
pure result
------------------------------------------------------------------------
unions :: (Ord a, Semigroup a, Semigroup b, Ord b)
=> [Map a (Set b)] -> Map a (Set b)
unions = foldl' union Map.empty
union :: (Ord a, Semigroup a, Semigroup b, Ord b)
=> Map a (Set b) -> Map a (Set b) -> Map a (Set b)
union m1 m2 = invertBack $ Map.unionWith (<>) (invert m1) (invert m2)
invert :: (Ord b, Semigroup a) => Map a (Set b) -> Map b a
invert = Map.unionsWith (<>)
. (map (\(k,ss) -> Map.fromSet (\_ -> k) ss))
. Map.toList
invertBack :: (Ord a, Ord b) => Map b a -> Map a (Set b)
invertBack = Map.fromListWith (<>)
. (map (\(b,a) -> (a, Set.singleton b)))
. Map.toList
------------------------------------------------------------------------
termsByList :: ListType -> (Map (Maybe ListType) (Set Text)) -> Set Text termsByList :: ListType -> (Map (Maybe ListType) (Set Text)) -> Set Text
termsByList CandidateTerm m = Set.unions termsByList CandidateTerm m = Set.unions
...@@ -67,7 +86,6 @@ termsByList l m = ...@@ -67,7 +86,6 @@ termsByList l m =
fromMaybe Set.empty $ Map.lookup (Just l) m fromMaybe Set.empty $ Map.lookup (Just l) m
flowSocialListByMode :: ( RepoCmdM env err m flowSocialListByMode :: ( RepoCmdM env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
...@@ -81,8 +99,10 @@ flowSocialListByMode mode user nt ngrams' = do ...@@ -81,8 +99,10 @@ flowSocialListByMode mode user nt ngrams' = do
[] -> pure $ Map.fromList [(Nothing, ngrams')] [] -> pure $ Map.fromList [(Nothing, ngrams')]
_ -> do _ -> do
counts <- countFilterList ngrams' nt listIds Map.empty counts <- countFilterList ngrams' nt listIds Map.empty
-- printDebug "flowSocialListByMode counts" counts printDebug "flowSocialListByMode counts" counts
pure $ toSocialList counts ngrams' let r = toSocialList counts ngrams'
printDebug "flowSocialListByMode r" r
pure r
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
-- TODO: maybe use social groups too -- TODO: maybe use social groups too
...@@ -107,6 +127,16 @@ toSocialList1 m t = case Map.lookup t m of ...@@ -107,6 +127,16 @@ toSocialList1 m t = case Map.lookup t m of
, Set.singleton t , Set.singleton t
) )
toSocialList1_testIsTrue :: Bool
toSocialList1_testIsTrue = result == (Just MapTerm, Set.singleton token)
where
result = toSocialList1 (Map.fromList [(token, m)]) token
token = "token"
m = Map.fromList [ (CandidateTerm, 1)
, (MapTerm , 2)
, (StopTerm , 3)
]
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
-- | [ListId] does not merge the lists (it is for Master and User lists -- | [ListId] does not merge the lists (it is for Master and User lists
-- here we need UserList only -- here we need UserList only
......
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