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

[FIX:SocialList] API connection

parent 34b10326
...@@ -90,10 +90,15 @@ buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do ...@@ -90,10 +90,15 @@ buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do
<- flowSocialList' MySelfFirst user nt (Set.fromList $ Map.keys ngs') <- flowSocialList' MySelfFirst user nt (Set.fromList $ Map.keys ngs')
-- PrivateFirst for first developments since Public NodeMode is not implemented yet -- PrivateFirst for first developments since Public NodeMode is not implemented yet
-- printDebug "flowSocialList'" socialLists'
let let
groupParams = GroupedTextParams groupIt (Set.size . snd) fst snd {-(size . fst)-} groupParams = GroupedTextParams groupIt (Set.size . snd) fst snd {-(size . fst)-}
groupedWithList = toGroupedText groupParams socialLists' ngs' groupedWithList = toGroupedText groupParams socialLists' ngs'
printDebug "groupedWithList" groupedWithList
let
(stopTerms, tailTerms) = Map.partition (\t -> t ^. gt_listType == Just StopTerm) groupedWithList (stopTerms, tailTerms) = Map.partition (\t -> t ^. gt_listType == Just StopTerm) groupedWithList
(mapTerms, tailTerms') = Map.partition (\t -> t ^. gt_listType == Just MapTerm) tailTerms (mapTerms, tailTerms') = Map.partition (\t -> t ^. gt_listType == Just MapTerm) tailTerms
......
...@@ -14,7 +14,6 @@ Portability : POSIX ...@@ -14,7 +14,6 @@ Portability : POSIX
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
module Gargantext.Core.Text.List.Group.WithStem module Gargantext.Core.Text.List.Group.WithStem
where where
...@@ -68,8 +67,8 @@ data GroupedText score = ...@@ -68,8 +67,8 @@ data GroupedText score =
, _gt_size :: !Int , _gt_size :: !Int
, _gt_stem :: !Stem -- needed ? , _gt_stem :: !Stem -- needed ?
, _gt_nodes :: !(Set NodeId) , _gt_nodes :: !(Set NodeId)
} {-deriving Show--} } deriving Show --}
--{- {-
instance Show score => Show (GroupedText score) where instance Show score => Show (GroupedText score) where
show (GroupedText lt l s _ _ _ _) = show l <> " : " <> show lt <> " : " <> show s show (GroupedText lt l s _ _ _ _) = show l <> " : " <> show lt <> " : " <> show s
--} --}
...@@ -104,8 +103,16 @@ groupWithStem :: {- ( HasNgrams a ...@@ -104,8 +103,16 @@ groupWithStem :: {- ( HasNgrams a
=> -} GroupedTextParams a b => -} GroupedTextParams a b
-> Map Text (GroupedTextScores (Set NodeId)) -> Map Text (GroupedTextScores (Set NodeId))
-> Map Stem (GroupedText Int) -> Map Stem (GroupedText Int)
groupWithStem _ = undefined -- TODO (just for tests on Others Ngrams which do not need stem) groupWithStem _ = Map.mapWithKey scores2groupedText
scores2groupedText :: Text -> GroupedTextScores (Set NodeId) -> GroupedText Int
scores2groupedText t g = GroupedText (view gts_listType g)
t
(Set.size $ view gts_score g)
(Set.delete t $ view gts_children g)
(size t)
t
(view gts_score g)
------------------------------------------------------------------------ ------------------------------------------------------------------------
ngramsGroup :: GroupParams ngramsGroup :: GroupParams
...@@ -139,5 +146,4 @@ groupedTextWithStem gparams from = ...@@ -139,5 +146,4 @@ groupedTextWithStem gparams from =
t' t'
((view gt_fun_nodeIds gparams') d) ((view gt_fun_nodeIds gparams') d)
) )
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -72,7 +72,7 @@ data FlowListScores = ...@@ -72,7 +72,7 @@ data FlowListScores =
-- You can add any score by incrementing this type -- You can add any score by incrementing this type
-- , _flc_score :: Map Score Int -- , _flc_score :: Map Score Int
} }
deriving (Generic) deriving (Show, Generic)
makeLenses ''FlowListScores makeLenses ''FlowListScores
......
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