Commit 701ef9ac authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] SocialList with TypeFamilies

parent 1461659b
...@@ -10,11 +10,13 @@ Portability : POSIX ...@@ -10,11 +10,13 @@ Portability : POSIX
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Gargantext.Core.Text.Group module Gargantext.Core.Text.Group
where where
import Control.Lens (makeLenses, set) import Control.Lens (makeLenses, set, (^.))
import Data.Set (Set) import Data.Set (Set)
import Data.Map (Map) import Data.Map (Map)
import Data.Text (Text) import Data.Text (Text)
...@@ -23,7 +25,7 @@ import Gargantext.Core.Text (size) ...@@ -23,7 +25,7 @@ import Gargantext.Core.Text (size)
import Gargantext.Core.Types (ListType(..)) -- (MasterCorpusId, UserCorpusId) import Gargantext.Core.Types (ListType(..)) -- (MasterCorpusId, UserCorpusId)
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Database.Admin.Types.Node (NodeId)
-- import Gargantext.Core.Text.List.Learn (Model(..)) -- import Gargantext.Core.Text.List.Learn (Model(..))
import Gargantext.Core.Text.List.Social.Group (FlowListScores) import Gargantext.Core.Text.List.Social.Group (FlowListScores(..), flc_lists)
import Gargantext.Core.Text.Terms.Mono.Stem (stem) import Gargantext.Core.Text.Terms.Mono.Stem (stem)
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Set as Set import qualified Data.Set as Set
...@@ -115,24 +117,62 @@ grouping (GroupedText lt1 label1 score1 group1 s1 stem1 nodes1) ...@@ -115,24 +117,62 @@ grouping (GroupedText lt1 label1 score1 group1 s1 stem1 nodes1)
nodes = Set.union nodes1 nodes2 nodes = Set.union nodes1 nodes2
------------------------------------------------------------------------ ------------------------------------------------------------------------
toGroupedText_FlowListScores :: ( FlowList a
toGroupedText_FlowListScores :: Ord a , Ord a
=> Map Text (Set NodeId) )
=> [a]
-> Map Text FlowListScores -> Map Text FlowListScores
-> Map Text (GroupedText a) -> Map Text (GroupedText b)
toGroupedText_FlowListScores = undefined toGroupedText_FlowListScores = undefined
toGroupedText_FlowListScores' :: ( FlowList a
toGroupedText_FlowListScores' :: Ord a , b ~ GroupFamily a
=> Map Text (Set NodeId) )
-> Map Text FlowListScores => [a]
-> ( [(Text, Set NodeId)] -> Map Text FlowListScores
, Map Text (GroupedText a) -> ( [a]
) , Map Text (GroupedText b)
toGroupedText_FlowListScores' = undefined )
toGroupedText_FlowListScores' ms mf = foldl' fun_group start ms
where
start = ([], Map.empty)
fun_group (left, grouped) current =
case Map.lookup (hasNgrams current) mf of
Just scores -> (left, Map.alter (updateWith scores current) (hasNgrams current) grouped)
Nothing -> (current : left, grouped)
updateWith scores current Nothing = Just $ createGroupWith scores current
updateWith scores current (Just x) = Just $ updateGroupWith scores current x
type FlowList a = (HasNgrams a, HasGroup a)
class HasNgrams a where
hasNgrams :: a -> Text
class HasGroup a where
createGroupWith :: (b ~ GroupFamily a) => FlowListScores -> a -> GroupedText b
updateGroupWith :: (b ~ GroupFamily a)
=> FlowListScores -> a
-> GroupedText b
-> GroupedText b
-- | Check if functional dependency is better
type family GroupFamily a
type instance GroupFamily (Text, Set NodeId) = Int
------------------------------------------
instance HasGroup (Text, Set NodeId) where
createGroupWith fs (t, ns) = GroupedText (mapMax $ fs ^. flc_lists)
t
(Set.size ns)
Set.empty
(size t)
t
ns
updateGroupWith fs (t, ns) g = undefined
mapMax :: Map a b -> Maybe a
mapMax m = (fst . fst) <$> Map.maxViewWithKey m
------------------------------------------------------------------------ ------------------------------------------------------------------------
type Stem = Text type Stem = Text
type Label = Text type Label = Text
......
...@@ -84,7 +84,7 @@ buildNgramsOthersList ::( HasNodeError err ...@@ -84,7 +84,7 @@ buildNgramsOthersList ::( HasNodeError err
buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do
ngs' :: Map Text (Set NodeId) <- getNodesByNgramsUser uCid nt ngs' :: Map Text (Set NodeId) <- getNodesByNgramsUser uCid nt
socialLists' :: Map Text FlowListScores socialLists' :: Map Text FlowListScores
<- 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
......
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