Commit bb8a678f authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] Social List computations

parent 45d49b0f
...@@ -96,24 +96,23 @@ buildNgramsOthersList :: (-- RepoCmdM env err m ...@@ -96,24 +96,23 @@ buildNgramsOthersList :: (-- RepoCmdM env err m
-> (Text -> Text) -> (Text -> Text)
-> NgramsType -> NgramsType
-> Cmd err (Map NgramsType [NgramsElement]) -> Cmd err (Map NgramsType [NgramsElement])
buildNgramsOthersList user uCid groupIt nt = do buildNgramsOthersList _user uCid groupIt nt = do
ngs <- groupNodesByNgramsWith groupIt <$> getNodesByNgramsUser uCid nt ngs <- groupNodesByNgramsWith groupIt <$> getNodesByNgramsUser uCid nt
let let
listSize = 9 listSize = 9
all' = List.reverse all' = List.sortOn (Down . Set.size . snd . snd)
$ List.sortOn (Set.size . snd . snd)
$ Map.toList ngs $ Map.toList ngs
graphTerms = List.take listSize all' (graphTerms, candiTerms) = List.splitAt listSize all'
candiTerms = List.drop listSize all'
pure $ Map.unionsWith (<>) [ toElements MapTerm graphTerms pure $ Map.unionsWith (<>) [ toElements nt MapTerm graphTerms
, toElements CandidateTerm candiTerms , toElements nt CandidateTerm candiTerms
] ]
where
toElements nType x = toElements :: Ord k => k -> ListType -> [(Text, b)] -> Map k [NgramsElement]
Map.fromList [(nt, [ mkNgramsElement (NgramsTerm t) nType Nothing (mSetFromList []) toElements nType lType x =
Map.fromList [(nType, [ mkNgramsElement (NgramsTerm t) lType Nothing (mSetFromList [])
| (t, _ns) <- x | (t, _ns) <- x
] ]
)] )]
...@@ -132,7 +131,7 @@ buildNgramsTermsList :: ( HasNodeError err ...@@ -132,7 +131,7 @@ buildNgramsTermsList :: ( HasNodeError err
-> UserCorpusId -> UserCorpusId
-> MasterCorpusId -> MasterCorpusId
-> m (Map NgramsType [NgramsElement]) -> m (Map NgramsType [NgramsElement])
buildNgramsTermsList user l n m s uCid mCid = do buildNgramsTermsList user l n m _s uCid mCid = do
-- Computing global speGen score -- Computing global speGen score
allTerms <- Map.toList <$> getTficf uCid mCid NgramsTerms allTerms <- Map.toList <$> getTficf uCid mCid NgramsTerms
...@@ -141,11 +140,18 @@ buildNgramsTermsList user l n m s uCid mCid = do ...@@ -141,11 +140,18 @@ buildNgramsTermsList user l n m s uCid mCid = do
-- printDebug "tail candidates" (List.take 10 $ List.reverse $ allTerms) -- printDebug "tail candidates" (List.take 10 $ List.reverse $ allTerms)
-- First remove stops terms -- First remove stops terms
mapSocialList <- flowSocialList user NgramsTerms (Set.fromList $ map fst allTerms) socialLists <- flowSocialList user NgramsTerms (Set.fromList $ map fst allTerms)
printDebug "\n * socialLists * \n" socialLists
let let
_socialMap = fromMaybe Set.empty $ Map.lookup MapTerm socialLists
_socialCand = fromMaybe Set.empty $ Map.lookup CandidateTerm socialLists
socialStop = fromMaybe Set.empty $ Map.lookup StopTerm socialLists
-- stopTerms ignored for now (need to be tagged already) -- stopTerms ignored for now (need to be tagged already)
(_stopTerms, candidateTerms) = List.partition ((isStopTerm s) . fst) allTerms (stopTerms, candidateTerms) = List.partition ((\t -> Set.member t socialStop) . fst) allTerms
printDebug "stopTerms" stopTerms
-- Grouping the ngrams and keeping the maximum score for label -- Grouping the ngrams and keeping the maximum score for label
let grouped = groupStems' let grouped = groupStems'
...@@ -280,11 +286,12 @@ buildNgramsTermsList user l n m s uCid mCid = do ...@@ -280,11 +286,12 @@ buildNgramsTermsList user l n m s uCid mCid = do
printDebug "multScoredInclHead" multScoredInclHead printDebug "multScoredInclHead" multScoredInclHead
printDebug "multScoredExclTail" multScoredExclTail printDebug "multScoredExclTail" multScoredExclTail
pure $ Map.unionsWith (<>)
[ Map.fromList [(
pure $ Map.fromList [(NgramsTerms, (List.concat $ map toNgramsElement $ termListHead) NgramsTerms, (List.concat $ map toNgramsElement $ termListHead)
<> (List.concat $ map toNgramsElement $ termListTail) <> (List.concat $ map toNgramsElement $ termListTail)
) )]
, toElements NgramsTerms StopTerm stopTerms
] ]
groupStems :: [(Stem, GroupedText Double)] -> [GroupedText Double] groupStems :: [(Stem, GroupedText Double)] -> [GroupedText Double]
......
...@@ -43,32 +43,31 @@ flowSocialList :: ( RepoCmdM env err m ...@@ -43,32 +43,31 @@ flowSocialList :: ( RepoCmdM env err m
=> User -> NgramsType -> Set Text => User -> NgramsType -> Set Text
-> m (Map ListType (Set Text)) -> m (Map ListType (Set Text))
flowSocialList user nt ngrams' = do flowSocialList user nt ngrams' = do
privateMapList <- flowSocialListByMode Private user nt ngrams' privateLists <- flowSocialListByMode Private user nt ngrams'
sharedMapList <- flowSocialListByMode Shared user nt (termsByList CandidateTerm privateMapList) printDebug "* privateLists *: \n" privateLists
sharedLists <- flowSocialListByMode Shared user nt (termsByList CandidateTerm privateLists)
printDebug "* socialLists *: \n" sharedLists
-- TODO publicMapList -- TODO publicMapList
pure $ Map.fromList [ (MapTerm, termsByList MapTerm privateMapList pure $ Map.fromList [ (MapTerm, termsByList MapTerm privateLists
<> termsByList MapTerm sharedMapList <> termsByList MapTerm sharedLists
) )
, (StopTerm, termsByList StopTerm privateMapList , (StopTerm, termsByList StopTerm privateLists
<> termsByList StopTerm sharedMapList <> termsByList StopTerm sharedLists
) )
, (CandidateTerm, termsByList CandidateTerm sharedMapList) , (CandidateTerm, termsByList CandidateTerm sharedLists)
] ]
termsByList :: ListType -> (Map (Maybe ListType) (Set Text)) -> Set Text termsByList :: ListType -> (Map (Maybe ListType) (Set Text)) -> Set Text
termsByList CandidateTerm m = termsByList CandidateTerm m = Set.unions
fromMaybe Set.empty $ map (\lt -> fromMaybe Set.empty $ Map.lookup lt m)
$ (<>) <$> Map.lookup Nothing m [ Nothing, Just CandidateTerm ]
<*> Map.lookup (Just CandidateTerm) m
termsByList l m = 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
...@@ -78,7 +77,11 @@ flowSocialListByMode :: ( RepoCmdM env err m ...@@ -78,7 +77,11 @@ flowSocialListByMode :: ( RepoCmdM env err m
-> m (Map (Maybe ListType) (Set Text)) -> m (Map (Maybe ListType) (Set Text))
flowSocialListByMode mode user nt ngrams' = do flowSocialListByMode mode user nt ngrams' = do
listIds <- findListsId mode user listIds <- findListsId mode user
case listIds of
[] -> pure $ Map.fromList [(Nothing, ngrams')]
_ -> do
counts <- countFilterList ngrams' nt listIds Map.empty counts <- countFilterList ngrams' nt listIds Map.empty
printDebug "flowSocialListByMode counts" counts
pure $ toSocialList counts ngrams' pure $ toSocialList counts ngrams'
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
...@@ -121,23 +124,33 @@ countFilterList' :: RepoCmdM env err m ...@@ -121,23 +124,33 @@ countFilterList' :: RepoCmdM env err m
-> m (Map Text (Map ListType Int)) -> m (Map Text (Map ListType Int))
countFilterList' st nt ls input = do countFilterList' st nt ls input = do
ml <- toMapTextListType <$> getListNgrams ls nt ml <- toMapTextListType <$> getListNgrams ls nt
printDebug "countFilterList'" ml
pure $ Set.foldl' (\m t -> countList t ml m) input st pure $ Set.foldl' (\m t -> countList t ml m) input st
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
-- FIXME children have to herit the ListType of the parent
toMapTextListType :: Map Text NgramsRepoElement -> Map Text ListType toMapTextListType :: Map Text NgramsRepoElement -> Map Text ListType
toMapTextListType = Map.fromListWith (<>) toMapTextListType m = Map.fromListWith (<>)
. List.concat $ List.concat
. (map toList) $ (map (toList m))
. Map.toList $ Map.toList m
toList :: (Text, NgramsRepoElement) -> [(Text, ListType)] listOf :: Map Text NgramsRepoElement -> NgramsRepoElement -> ListType
toList (t, NgramsRepoElement _ lt root parent (MSet children)) = listOf m ng = case _nre_parent ng of
List.zip terms (List.cycle [lt]) Nothing -> _nre_list ng
Just p -> case Map.lookup (unNgramsTerm p) m of
Nothing -> CandidateTerm -- Should Not happen
Just ng' -> listOf m ng'
toList :: Map Text NgramsRepoElement -> (Text, NgramsRepoElement) -> [(Text, ListType)]
toList m (t, nre@(NgramsRepoElement _ _ _ _ (MSet children))) =
List.zip terms (List.cycle [lt'])
where where
terms = [t] terms = [t]
<> maybe [] (\n -> [unNgramsTerm n]) root -- <> maybe [] (\n -> [unNgramsTerm n]) root
<> maybe [] (\n -> [unNgramsTerm n]) parent -- <> maybe [] (\n -> [unNgramsTerm n]) parent
<> (map unNgramsTerm $ Map.keys children) <> (map unNgramsTerm $ Map.keys children)
lt' = listOf m nre
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
countList :: Text countList :: Text
...@@ -162,12 +175,17 @@ findListsId :: (HasNodeError err, HasTreeError err) ...@@ -162,12 +175,17 @@ findListsId :: (HasNodeError err, HasTreeError err)
=> NodeMode -> User -> Cmd err [NodeId] => NodeMode -> User -> Cmd err [NodeId]
findListsId mode u = do findListsId mode u = do
r <- getRootId u r <- getRootId u
map _dt_nodeId <$> filter (\n -> _dt_typeId n == nodeTypeId NodeList) ns <- map _dt_nodeId <$> filter (\n -> _dt_typeId n == nodeTypeId NodeList)
<$> findNodes' mode r <$> findNodes' mode r
printDebug "findListsIds" ns
pure ns
commonNodes:: [NodeType]
commonNodes = [NodeFolder, NodeCorpus, NodeList]
findNodes' :: HasTreeError err findNodes' :: HasTreeError err
=> NodeMode -> RootId => NodeMode -> RootId
-> Cmd err [DbTreeNode] -> Cmd err [DbTreeNode]
findNodes' Private r = findNodes Private r [NodeFolderPrivate, NodeCorpus, NodeList] findNodes' Private r = findNodes Private r $ [NodeFolderPrivate] <> commonNodes
findNodes' Shared r = findNodes Shared r [NodeFolderShared , NodeCorpus, NodeList] findNodes' Shared r = findNodes Shared r $ [NodeFolderShared ] <> commonNodes
findNodes' Public r = findNodes Public r [NodeFolderPublic , NodeCorpus, NodeList] findNodes' Public r = findNodes Public r $ [NodeFolderPublic ] <> commonNodes
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