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

Merge branch 'dev-social-list' into dev

parents d443a173 8d9f7145
...@@ -25,7 +25,7 @@ import Data.Time (UTCTime) ...@@ -25,7 +25,7 @@ import Data.Time (UTCTime)
import Servant import Servant
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams.NTree import Gargantext.API.Ngrams.NgramsTree
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..)) import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..))
...@@ -317,7 +317,7 @@ type TreeApi = Summary " Tree API" ...@@ -317,7 +317,7 @@ type TreeApi = Summary " Tree API"
:> QueryParam "list" ListId :> QueryParam "list" ListId
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParamR "listType" ListType :> QueryParamR "listType" ListType
:> Get '[JSON] (HashedResponse (ChartMetrics [MyTree])) :> Get '[JSON] (HashedResponse (ChartMetrics [NgramsTree]))
:<|> Summary "Tree Chart update" :<|> Summary "Tree Chart update"
:> QueryParam "list" ListId :> QueryParam "list" ListId
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
...@@ -347,7 +347,7 @@ getTree :: FlowCmdM env err m ...@@ -347,7 +347,7 @@ getTree :: FlowCmdM env err m
-> Maybe ListId -> Maybe ListId
-> TabType -> TabType
-> ListType -> ListType
-> m (HashedResponse (ChartMetrics [MyTree])) -> m (HashedResponse (ChartMetrics [NgramsTree]))
getTree cId _start _end maybeListId tabType listType = do getTree cId _start _end maybeListId tabType listType = do
listId <- case maybeListId of listId <- case maybeListId of
Just lid -> pure lid Just lid -> pure lid
...@@ -383,7 +383,7 @@ updateTree' :: FlowCmdM env err m => ...@@ -383,7 +383,7 @@ updateTree' :: FlowCmdM env err m =>
-> Maybe ListId -> Maybe ListId
-> TabType -> TabType
-> ListType -> ListType
-> m (ChartMetrics [MyTree]) -> m (ChartMetrics [NgramsTree])
updateTree' cId maybeListId tabType listType = do updateTree' cId maybeListId tabType listType = do
listId <- case maybeListId of listId <- case maybeListId of
Just lid -> pure lid Just lid -> pure lid
......
{-# OPTIONS_GHC -fno-warn-unused-top-binds #-}
{-| {-|
Module : Gargantext.API.Ngrams Module : Gargantext.API.Ngrams
Description : Server API Description : Server API
...@@ -16,6 +15,8 @@ add get ...@@ -16,6 +15,8 @@ add get
-} -}
{-# OPTIONS_GHC -fno-warn-unused-top-binds #-}
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
...@@ -307,6 +308,10 @@ commitStatePatch (Versioned p_version p) = do ...@@ -307,6 +308,10 @@ commitStatePatch (Versioned p_version p) = do
pure (r', Versioned (r' ^. r_version) q') pure (r', Versioned (r' ^. r_version) q')
saveRepo saveRepo
-- Save new ngrams
_ <- insertNgrams (newNgramsFromNgramsStatePatch p)
pure vq' pure vq'
-- This is a special case of tableNgramsPut where the input patch is empty. -- This is a special case of tableNgramsPut where the input patch is empty.
......
{-| {-|
Module : Gargantext.API.Ngrams.NTree Module : Gargantext.API.Ngrams.NgramsTree
Description : Tree of Ngrams Description : Tree of Ngrams
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -11,7 +11,7 @@ Portability : POSIX ...@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Ngrams.NTree module Gargantext.API.Ngrams.NgramsTree
where where
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
...@@ -36,24 +36,25 @@ import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) ...@@ -36,24 +36,25 @@ import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
type Children = Text type Children = Text
type Root = Text type Root = Text
data MyTree = MyTree { mt_label :: Text data NgramsTree = NgramsTree { mt_label :: Text
, mt_value :: Double , mt_value :: Double
, mt_children :: [MyTree] , mt_children :: [NgramsTree]
} deriving (Generic, Show) }
deriving (Generic, Show)
toMyTree :: Tree (Text,Double) -> MyTree toNgramsTree :: Tree (Text,Double) -> NgramsTree
toMyTree (Node (l,v) xs) = MyTree l v (map toMyTree xs) toNgramsTree (Node (l,v) xs) = NgramsTree l v (map toNgramsTree xs)
deriveJSON (unPrefix "mt_") ''MyTree deriveJSON (unPrefix "mt_") ''NgramsTree
instance ToSchema MyTree where instance ToSchema NgramsTree where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "mt_") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "mt_")
instance Arbitrary MyTree instance Arbitrary NgramsTree
where where
arbitrary = MyTree <$> arbitrary <*> arbitrary <*> arbitrary arbitrary = NgramsTree <$> arbitrary <*> arbitrary <*> arbitrary
toTree :: ListType -> Map Text (Set NodeId) -> Map Text NgramsRepoElement -> [MyTree] toTree :: ListType -> Map Text (Set NodeId) -> Map Text NgramsRepoElement -> [NgramsTree]
toTree lt vs m = map toMyTree $ unfoldForest buildNode roots toTree lt vs m = map toNgramsTree $ unfoldForest buildNode roots
where where
buildNode r = maybe ((r, value r),[]) buildNode r = maybe ((r, value r),[])
(\x -> ((r, value r), unNgramsTerm <$> (mSetToList $ _nre_children x))) (\x -> ((r, value r), unNgramsTerm <$> (mSetToList $ _nre_children x)))
......
...@@ -50,7 +50,7 @@ import Gargantext.Core.Text (size) ...@@ -50,7 +50,7 @@ import Gargantext.Core.Text (size)
import Gargantext.Core.Types (ListType(..), ListId, NodeId) import Gargantext.Core.Types (ListType(..), ListId, NodeId)
import Gargantext.Core.Types (TODO) import Gargantext.Core.Types (TODO)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema)
import Gargantext.Database.Prelude (fromField', CmdM') import Gargantext.Database.Prelude (fromField', CmdM', HasConnectionPool, HasConfig)
import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -706,8 +706,10 @@ instance HasRepoSaver RepoEnv where ...@@ -706,8 +706,10 @@ instance HasRepoSaver RepoEnv where
repoSaver = renv_saver repoSaver = renv_saver
type RepoCmdM env err m = type RepoCmdM env err m =
( CmdM' env err m ( CmdM' env err m
, HasRepo env , HasRepo env
, HasConnectionPool env
, HasConfig env
) )
......
This diff is collapsed.
...@@ -13,94 +13,67 @@ Portability : POSIX ...@@ -13,94 +13,67 @@ Portability : POSIX
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE InstanceSigs #-}
module Gargantext.Core.Text.List.Group module Gargantext.Core.Text.List.Group
where where
import Control.Lens (set) import Control.Lens (view)
import Data.Set (Set)
import Data.Map (Map) import Data.Map (Map)
import Data.Maybe (fromMaybe)
import Data.Monoid (Monoid, mempty)
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Core.Types (ListType(..)) import Gargantext.Core.Text.List.Social.Prelude
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Core.Text.List.Group.Prelude
import Gargantext.Core.Text.List.Social.Scores (FlowListScores(..))
import Gargantext.Core.Text.List.Group.WithStem import Gargantext.Core.Text.List.Group.WithStem
import Gargantext.Core.Text.List.Group.WithScores import Gargantext.Core.Text.List.Group.WithScores
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Set as Set
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.List as List
------------------------------------------------------------------------ ------------------------------------------------------------------------
toGroupedText :: GroupedTextParams a b -- | TODO add group with stemming
-> Map Text FlowListScores toGroupedTree :: (Ord a, Monoid a, GroupWithStem a)
-> Map Text (Set NodeId) => GroupParams
-> Map Stem (GroupedText Int) -> FlowCont Text FlowListScores
toGroupedText groupParams scores = -> Map Text a
(groupWithStem groupParams) . (groupWithScores scores) -- -> Map Text (GroupedTreeScores (Set NodeId))
-> FlowCont Text (GroupedTreeScores a)
toGroupedTree groupParams flc scores = {-view flc_scores-} flow2
------------------------------------------------------------------------
-- | WIP
toGroupedText_test :: Bool -- Map Stem (GroupedText Int)
toGroupedText_test =
-- fromGroupedScores $ fromListScores from
toGroupedText params from datas == result
where where
params = GroupedTextParams identity (Set.size . snd) fst snd flow1 = groupWithScores' flc scoring
from :: Map Text FlowListScores scoring t = fromMaybe mempty $ Map.lookup t scores
from = Map.fromList [("A. Rahmani",FlowListScores {_fls_parents = Map.fromList [("T. Reposeur",1)]
,_fls_listType = Map.fromList [(MapTerm,2)]})
,("B. Tamain",FlowListScores {_fls_parents = Map.fromList [("T. Reposeur",1)]
, _fls_listType = Map.fromList [(MapTerm,2)]})
]
datas :: Map Text (Set NodeId) flow2 = case (view flc_cont flow1) == Map.empty of
datas = Map.fromList [("A. Rahmani" , Set.fromList [1,2]) True -> flow1
,("T. Reposeur", Set.fromList [3,4]) False -> groupWithStem' groupParams flow1
,("B. Tamain" , Set.fromList [5,6])
]
result :: Map Stem (GroupedText Int)
result = Map.fromList [("A. Rahmani",GroupedText {_gt_listType = Nothing
,_gt_label = "A. Rahmani"
,_gt_score = 2
,_gt_children = Set.empty
,_gt_size = 2
,_gt_stem = "A. Rahmani"
,_gt_nodes = Set.fromList [1,2]
}
)
,("B. Tamain",GroupedText {_gt_listType = Nothing
, _gt_label = "B. Tamain"
, _gt_score = 2
, _gt_children = Set.empty
, _gt_size = 2
, _gt_stem = "B. Tamain"
, _gt_nodes = Set.fromList [5,6]
}
)
,("T. Reposeur",GroupedText {_gt_listType = Nothing
,_gt_label = "T. Reposeur"
,_gt_score = 2
,_gt_children = Set.fromList ["A. Rahmani","B. Tamain"]
,_gt_size = 2
,_gt_stem = "T. Reposeur"
,_gt_nodes = Set.fromList [1..6]
}
)
]
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | To be removed setScoresWithMap :: (Ord a, Ord b, Monoid b) => Map Text b
addListType :: Map Text ListType -> GroupedText a -> GroupedText a -> Map Text (GroupedTreeScores a)
addListType m g = set gt_listType (hasListType m g) g -> Map Text (GroupedTreeScores b)
setScoresWithMap m = setScoresWith (score m)
where where
hasListType :: Map Text ListType -> GroupedText a -> Maybe ListType score m' t = case Map.lookup t m' of
hasListType m' (GroupedText _ label _ g' _ _ _) = Nothing -> mempty
List.foldl' (<>) Nothing Just r -> r
$ map (\t -> Map.lookup t m')
$ Set.toList setScoresWith :: (Ord a, Ord b)
$ Set.insert label g' => (Text -> b)
-> Map Text (GroupedTreeScores a)
-> Map Text (GroupedTreeScores b)
{-
-- | This Type level lenses solution does not work
setScoresWith f = Map.mapWithKey (\k v -> over gts'_children (setScoresWith f)
$ set gts'_score (f k) v
)
-}
setScoresWith f = Map.mapWithKey (\k v -> v { _gts'_score = f k
, _gts'_children = setScoresWith f
$ view gts'_children v
}
)
------------------------------------------------------------------------
{-|
Module : Gargantext.Core.Text.List.Group.Prelude
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE InstanceSigs #-}
module Gargantext.Core.Text.List.Group.Prelude
where
import Control.Lens (makeLenses, view, set, over)
import Data.Monoid
import Data.Semigroup
import Data.Set (Set)
import Data.Text (Text)
import Data.Maybe (fromMaybe)
import Data.Map (Map)
import Gargantext.Core.Types (ListType(..))
import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Core.Text.Metrics (Scored(..), scored_genInc)
import Gargantext.API.Ngrams.Types (NgramsElement, mkNgramsElement, NgramsTerm(..), RootParent(..), mSetFromList)
import Gargantext.Prelude
import qualified Data.Set as Set
import qualified Data.Map as Map
import qualified Data.List as List
type Stem = Text
------------------------------------------------------------------------
-- | Main Types to group With Scores but preserving Tree dependencies
-- Therefore there is a need of Tree of GroupedTextScores
-- to target continuation type for the flow (FlowCont Text GroupedTreeScores)
data GroupedTreeScores score =
GroupedTreeScores { _gts'_listType :: !(Maybe ListType)
, _gts'_children :: !(Map Text (GroupedTreeScores score))
, _gts'_score :: !score
} deriving (Show, Ord, Eq)
instance (Semigroup a) => Semigroup (GroupedTreeScores a) where
(<>) (GroupedTreeScores l1 s1 c1)
(GroupedTreeScores l2 s2 c2)
= GroupedTreeScores (l1 <> l2)
(s1 <> s2)
(c1 <> c2)
instance (Ord score, Monoid score)
=> Monoid (GroupedTreeScores score) where
mempty = GroupedTreeScores mempty mempty mempty
makeLenses 'GroupedTreeScores
------------------------------------------------------------------------
-- | Main Classes
class ViewListType a where
viewListType :: a -> Maybe ListType
class SetListType a where
setListType :: Maybe ListType -> a -> a
------
class Ord b => ViewScore a b | a -> b where
viewScore :: a -> b
class ViewScores a b | a -> b where
viewScores :: a -> b
--------
class ToNgramsElement a where
toNgramsElement :: a -> [NgramsElement]
class HasTerms a where
hasTerms :: a -> Set Text
------------------------------------------------------------------------
-- | Instances declartion for (GroupedTreeScores a)
instance ViewListType (GroupedTreeScores a) where
viewListType = view gts'_listType
instance SetListType (GroupedTreeScores a) where
setListType lt g = over gts'_children (setListType lt)
$ set gts'_listType lt g
instance SetListType (Map Text (GroupedTreeScores a)) where
setListType lt = Map.map (set gts'_listType lt)
------
instance ViewScore (GroupedTreeScores Double) Double where
viewScore = viewScores
instance ViewScores (GroupedTreeScores Double) Double where
viewScores g = sum $ parent : children
where
parent = view gts'_score g
children = map viewScores $ Map.elems $ view gts'_children g
instance ViewScore (GroupedTreeScores (Set NodeId)) Int where
viewScore = Set.size . viewScores
instance ViewScores (GroupedTreeScores (Set NodeId)) (Set NodeId) where
viewScores g = Set.unions $ parent : children
where
parent = view gts'_score g
children = map viewScores $ Map.elems $ view gts'_children g
instance ViewScore (GroupedTreeScores (Scored Text)) Double where
viewScore = view (gts'_score . scored_genInc)
------
instance HasTerms (Map Text (GroupedTreeScores a)) where
hasTerms = Set.unions . (map hasTerms) . Map.toList
instance HasTerms (Text, GroupedTreeScores a) where
hasTerms (t, g) = Set.singleton t <> children
where
children = Set.unions
$ map hasTerms
$ Map.toList
$ view gts'_children g
------
instance ToNgramsElement (Map Text (GroupedTreeScores a)) where
toNgramsElement = List.concat . (map toNgramsElement) . Map.toList
instance ToNgramsElement (Text, GroupedTreeScores a) where
toNgramsElement (t, gts) = parent : children
where
parent = mkNgramsElement (NgramsTerm t)
(fromMaybe CandidateTerm $ viewListType gts)
Nothing
(mSetFromList $ map NgramsTerm
$ Map.keys
$ view gts'_children gts
)
children = List.concat
$ map (childrenWith (NgramsTerm t) (NgramsTerm t) )
$ Map.toList
$ view gts'_children gts
childrenWith root parent' (t', gts') = parent'' : children'
where
parent'' = mkNgramsElement (NgramsTerm t')
(fromMaybe CandidateTerm $ viewListType gts')
(Just $ RootParent root parent')
(mSetFromList $ map NgramsTerm
$ Map.keys
$ view gts'_children gts'
)
children' = List.concat
$ map (childrenWith root (NgramsTerm t') )
$ Map.toList
$ view gts'_children gts'
...@@ -10,116 +10,88 @@ Portability : POSIX ...@@ -10,116 +10,88 @@ Portability : POSIX
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE InstanceSigs #-}
module Gargantext.Core.Text.List.Group.WithScores module Gargantext.Core.Text.List.Group.WithScores
where where
import Control.Lens (makeLenses, view, set) import Control.Lens (view, set, over)
import Data.Semigroup import Data.Semigroup
import Data.Set (Set)
import Data.Map (Map) import Data.Map (Map)
import Data.Maybe (catMaybes) import Data.Monoid (Monoid, mempty)
import Data.Maybe (fromMaybe)
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Core.Types (ListType(..)) -- (MasterCorpusId, UserCorpusId) import Gargantext.Core.Text.List.Social.Prelude
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Core.Text.List.Group.Prelude
-- import Gargantext.Core.Text.List.Learn (Model(..))
import Gargantext.Core.Text.List.Social.Scores
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Set as Set
import qualified Data.Map as Map import qualified Data.Map as Map
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Main Types
data GroupedWithListScores =
GroupedWithListScores { _gwls_children :: !(Set Text)
, _gwls_listType :: !(Maybe ListType)
} deriving (Show)
makeLenses ''GroupedWithListScores
instance Semigroup GroupedWithListScores where
(<>) (GroupedWithListScores c1 l1)
(GroupedWithListScores c2 l2) =
GroupedWithListScores (c1 <> c2) (l1 <> l2)
------
data GroupedTextScores score =
GroupedTextScores { _gts_listType :: !(Maybe ListType)
, _gts_score :: score
, _gts_children :: !(Set Text)
} deriving (Show)
makeLenses 'GroupedTextScores
instance Semigroup a => Semigroup (GroupedTextScores a) where
(<>) (GroupedTextScores l1 s1 c1)
(GroupedTextScores l2 s2 c2)
= GroupedTextScores (l1 <> l2) (s1 <> s2) (c1 <> c2)
------
data GroupedTextScores' score =
GroupedTextScores' { _gts'_listType :: !(Maybe ListType)
, _gts'_score :: score
, _gts'_children :: !(Set (GroupedTextScores' score))
} deriving (Show, Ord, Eq)
makeLenses 'GroupedTextScores'
instance (Semigroup a, Ord a) => Semigroup (GroupedTextScores' a) where
(<>) (GroupedTextScores' l1 s1 c1)
(GroupedTextScores' l2 s2 c2)
= GroupedTextScores' (l1 <> l2) (s1 <> s2) (c1 <> c2)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Main function -- | Main function
groupWithScores :: Map Text FlowListScores groupWithScores' :: (Eq a, Ord a, Monoid a)
-> Map Text (Set NodeId) => FlowCont Text FlowListScores
-> Map Text (GroupedTextScores (Set NodeId)) -> (Text -> a) -- Map Text (a)
groupWithScores scores ms = orphans <> groups -> FlowCont Text (GroupedTreeScores (a))
groupWithScores' flc scores = FlowCont groups orphans
where where
groups = addScore ms -- parent/child relation is inherited from social lists
$ fromGroupedScores groups = toGroupedTree
$ fromListScores scores $ toMapMaybeParent scores
orphans = addIfNotExist scores ms $ view flc_scores flc
-- orphans should be filtered already
orphans = toGroupedTree
$ toMapMaybeParent scores
$ view flc_cont flc
------------------------------------------------------------------------
toMapMaybeParent :: (Eq a, Ord a, Monoid a)
=> (Text -> a)
-> Map Text FlowListScores
-> Map (Maybe Parent) (Map Text (GroupedTreeScores (a)))
toMapMaybeParent f = Map.fromListWith (<>)
. (map (fromScores'' f))
. Map.toList
fromScores'' :: (Eq a, Ord a, Monoid a)
=> (Text -> a)
-> (Text, FlowListScores)
-> (Maybe Parent, Map Text (GroupedTreeScores (a)))
fromScores'' f' (t, fs) = ( maybeParent
, Map.fromList [( t, set gts'_score (f' t)
$ set gts'_listType maybeList mempty
)]
)
where
maybeParent = keyWithMaxValue $ view fls_parents fs
maybeList = keyWithMaxValue $ view fls_listType fs
toGroupedTree :: Eq a
=> Map (Maybe Parent) (Map Text (GroupedTreeScores (a)))
-> Map Parent (GroupedTreeScores (a))
toGroupedTree m = case Map.lookup Nothing m of
Nothing -> mempty
Just m' -> toGroupedTree' m m'
toGroupedTree' :: Eq a => Map (Maybe Parent) (Map Text (GroupedTreeScores (a)))
-> (Map Text (GroupedTreeScores (a)))
-> Map Parent (GroupedTreeScores (a))
toGroupedTree' m notEmpty
| notEmpty == mempty = mempty
| otherwise = Map.mapWithKey (addGroup m) notEmpty
where
addGroup m' k v = over gts'_children ( (toGroupedTree' m')
. (Map.union ( fromMaybe mempty
$ Map.lookup (Just k) m'
)
)
)
v
addScore :: Map Text (Set NodeId)
-> Map Text (GroupedTextScores (Set NodeId))
-> Map Text (GroupedTextScores (Set NodeId))
addScore mapNs = Map.mapWithKey scoring
where
scoring k g = set gts_score ( Set.unions
$ catMaybes
$ map (\n -> Map.lookup n mapNs)
$ [k] <> (Set.toList $ view gts_children g)
) g
addIfNotExist :: Map Text FlowListScores
-> Map Text (Set NodeId)
-> Map Text (GroupedTextScores (Set NodeId))
addIfNotExist mapSocialScores mapScores =
foldl' (addIfNotExist' mapSocialScores) Map.empty $ Map.toList mapScores
where
addIfNotExist' mss m (t,ns) =
case Map.lookup t mss of
Nothing -> Map.alter (add ns) t m
_ -> m
add ns' Nothing = Just $ GroupedTextScores Nothing ns' Set.empty
add _ _ = Nothing -- should not be present
------------------------------------------------------------------------
fromGroupedScores :: Map Parent GroupedWithListScores
-> Map Parent (GroupedTextScores (Set NodeId))
fromGroupedScores = Map.map (\(GroupedWithListScores c l) -> GroupedTextScores l Set.empty c)
------------------------------------------------------------------------
fromListScores :: Map Text FlowListScores -> Map Parent GroupedWithListScores
fromListScores = Map.fromListWith (<>) . (map fromScores') . Map.toList
where
fromScores' :: (Text, FlowListScores) -> (Text, GroupedWithListScores)
fromScores' (t, fs) = case (keyWithMaxValue $ view fls_parents fs) of
Nothing -> (t, GroupedWithListScores Set.empty (keyWithMaxValue $ view fls_listType fs))
-- Parent case: taking its listType, for now children Set is empty
Just parent -> (parent, GroupedWithListScores (Set.singleton t) Nothing)
-- We ignore the ListType of children for the parents' one
-- added after and winner of semigroup actions
...@@ -11,60 +11,25 @@ Portability : POSIX ...@@ -11,60 +11,25 @@ Portability : POSIX
module Gargantext.Core.Text.List.Social module Gargantext.Core.Text.List.Social
where where
import Data.Map (Map) import Data.Monoid (mconcat)
import Data.Maybe (fromMaybe)
import Data.Semigroup (Semigroup(..))
import Data.Set (Set)
import Data.Text (Text) import Data.Text (Text)
import Gargantext.API.Ngrams.Tools -- (getListNgrams) import Gargantext.API.Ngrams.Tools
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Text.List.Social.Find import Gargantext.Core.Text.List.Social.Find
import Gargantext.Core.Text.List.Social.ListType import Gargantext.Core.Text.List.Social.Prelude
import Gargantext.Core.Text.List.Social.Scores import Gargantext.Core.Text.List.Social.Scores
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Core.Types.Main
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node.Error import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Tree import Gargantext.Database.Query.Tree
import Gargantext.Database.Schema.Ngrams import Gargantext.Database.Schema.Ngrams
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Map as Map
import qualified Data.Set as Set
------------------------------------------------------------------------
flowSocialList :: ( RepoCmdM env err m
, CmdM env err m
, HasNodeError err
, HasTreeError err
)
=> User -> NgramsType -> Set Text
-> m (Map ListType (Set Text))
flowSocialList user nt ngrams' = do
-- Here preference to privateLists (discutable: let user choice)
privateListIds <- findListsId user Private
privateLists <- flowSocialListByMode privateListIds nt ngrams'
-- printDebug "* privateLists *: \n" privateLists
sharedListIds <- findListsId user Shared
sharedLists <- flowSocialListByMode sharedListIds nt (termsByList CandidateTerm privateLists)
-- printDebug "* sharedLists *: \n" sharedLists
-- TODO publicMapList:
-- Note: if both produce 3 identic repetition => refactor mode
-- publicListIds <- findListsId Public user
-- publicLists <- flowSocialListByMode' publicListIds nt (termsByList CandidateTerm privateLists)
let result = parentUnionsExcl
[ Map.mapKeys (fromMaybe CandidateTerm) privateLists
, Map.mapKeys (fromMaybe CandidateTerm) sharedLists
-- , Map.mapKeys (fromMaybe CandidateTerm) publicLists
]
-- printDebug "* socialLists *: results \n" result
pure result
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Main parameters
-- | FlowSocialListPriority -- | FlowSocialListPriority
-- Sociological assumption: either private or others (public) first -- Sociological assumption: either private or others (public) first
-- This parameter depends on the user choice -- This parameter depends on the user choice
...@@ -74,58 +39,6 @@ flowSocialListPriority :: FlowSocialListPriority -> [NodeMode] ...@@ -74,58 +39,6 @@ flowSocialListPriority :: FlowSocialListPriority -> [NodeMode]
flowSocialListPriority MySelfFirst = [Private, Shared{-, Public -}] flowSocialListPriority MySelfFirst = [Private, Shared{-, Public -}]
flowSocialListPriority OthersFirst = reverse $ flowSocialListPriority MySelfFirst flowSocialListPriority OthersFirst = reverse $ flowSocialListPriority MySelfFirst
------------------------------------------------------------------------
flowSocialList' :: ( RepoCmdM env err m
, CmdM env err m
, HasNodeError err
, HasTreeError err
)
=> FlowSocialListPriority
-> User -> NgramsType -> Set Text
-> m (Map Text FlowListScores)
flowSocialList' flowPriority user nt ngrams' =
parentUnionsExcl <$> mapM (flowSocialListByMode' user nt ngrams')
(flowSocialListPriority flowPriority)
------------------------------------------------------------------------
flowSocialListByMode :: ( RepoCmdM env err m
, CmdM env err m
, HasNodeError err
, HasTreeError err
)
=> [NodeId]-> NgramsType -> Set Text
-> m (Map (Maybe ListType) (Set Text))
flowSocialListByMode [] _nt ngrams' = pure $ Map.fromList [(Nothing, ngrams')]
flowSocialListByMode listIds nt ngrams' = do
counts <- countFilterList ngrams' nt listIds Map.empty
let r = toSocialList counts ngrams'
pure r
flowSocialListByMode' :: ( RepoCmdM env err m
, CmdM env err m
, HasNodeError err
, HasTreeError err
)
=> User -> NgramsType -> Set Text -> NodeMode
-> m (Map Text FlowListScores)
flowSocialListByMode' user nt st mode =
findListsId user mode
>>= flowSocialListByModeWith nt st
flowSocialListByModeWith :: ( RepoCmdM env err m
, CmdM env err m
, HasNodeError err
, HasTreeError err
)
=> NgramsType -> Set Text -> [NodeId]
-> m (Map Text FlowListScores)
flowSocialListByModeWith nt st ns =
mapM (\l -> getListNgrams [l] nt) ns
>>= pure
. toFlowListScores (keepAllParents nt) st Map.empty
-- | We keep the parents for all ngrams but terms -- | We keep the parents for all ngrams but terms
keepAllParents :: NgramsType -> KeepAllParents keepAllParents :: NgramsType -> KeepAllParents
...@@ -133,67 +46,44 @@ keepAllParents NgramsTerms = KeepAllParents False ...@@ -133,67 +46,44 @@ keepAllParents NgramsTerms = KeepAllParents False
keepAllParents _ = KeepAllParents True keepAllParents _ = KeepAllParents True
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO: maybe use social groups too flowSocialList' :: ( RepoCmdM env err m
-- | TODO what if equality ? , CmdM env err m
-- choice depends on Ord instance of ListType , HasNodeError err
-- for now : data ListType = StopTerm | CandidateTerm | MapTerm , HasTreeError err
-- means MapTerm > CandidateTerm > StopTerm in case of equality of counts )
-- (we minimize errors on MapTerms if doubt) => FlowSocialListPriority
toSocialList :: Map Text (Map ListType Int) -> User -> NgramsType
-> Set Text -> FlowCont Text FlowListScores
-> Map (Maybe ListType) (Set Text) -> m (FlowCont Text FlowListScores)
toSocialList m = Map.fromListWith (<>) flowSocialList' flowPriority user nt flc =
. Set.toList mconcat <$> mapM (flowSocialListByMode' user nt flc)
. Set.map (toSocialList1 m) (flowSocialListPriority flowPriority)
where
toSocialList1 :: Map Text (Map ListType Int)
-> Text flowSocialListByMode' :: ( RepoCmdM env err m
-> (Maybe ListType, Set Text) , CmdM env err m
toSocialList1 m t = case Map.lookup t m of , HasNodeError err
Nothing -> (Nothing, Set.singleton t) , HasTreeError err
Just m' -> ( (fst . fst) <$> Map.maxViewWithKey m' )
, Set.singleton t => User -> NgramsType
) -> FlowCont Text FlowListScores
-> NodeMode
toSocialList1_testIsTrue :: Bool -> m (FlowCont Text FlowListScores)
toSocialList1_testIsTrue = result == (Just MapTerm, Set.singleton token) flowSocialListByMode' user' nt' flc' mode =
where findListsId user' mode
result = toSocialList1 (Map.fromList [(token, m)]) token >>= flowSocialListByModeWith nt' flc'
token = "token"
m = Map.fromList [ (CandidateTerm, 1)
, (MapTerm , 2) flowSocialListByModeWith :: ( RepoCmdM env err m
, (StopTerm , 3) , CmdM env err m
] , HasNodeError err
, HasTreeError err
------------------------------------------------------------------------ )
-- | Tools => NgramsType
------------------------------------------------------------------------ -> FlowCont Text FlowListScores
termsByList :: ListType -> (Map (Maybe ListType) (Set Text)) -> Set Text -> [NodeId]
termsByList CandidateTerm m = Set.unions -> m (FlowCont Text FlowListScores)
$ map (\lt -> fromMaybe Set.empty $ Map.lookup lt m) flowSocialListByModeWith nt'' flc'' ns =
[ Nothing, Just CandidateTerm ] mapM (\l -> getListNgrams [l] nt'') ns
termsByList l m = >>= pure
fromMaybe Set.empty $ Map.lookup (Just l) m . toFlowListScores (keepAllParents nt'') flc''
------------------------------------------------------------------------
unions :: (Ord a, Semigroup a, Semigroup b, Ord b)
=> [Map a (Set b)] -> Map a (Set b)
unions = invertBack . Map.unionsWith (<>) . map invertForw
invertForw :: (Ord b, Semigroup a) => Map a (Set b) -> Map b a
invertForw = Map.unionsWith (<>)
. (map (\(k,sets) -> Map.fromSet (\_ -> k) sets))
. 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
unions_test :: Map ListType (Set Text)
unions_test = unions [m1, m2]
where
m1 = Map.fromList [ (StopTerm , Set.singleton "Candidate")]
m2 = Map.fromList [ (CandidateTerm, Set.singleton "Candidate")
, (MapTerm , Set.singleton "Candidate")
]
...@@ -12,6 +12,7 @@ module Gargantext.Core.Text.List.Social.Find ...@@ -12,6 +12,7 @@ module Gargantext.Core.Text.List.Social.Find
where where
-- findList imports -- findList imports
import Control.Lens (view)
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Database.Admin.Config import Gargantext.Database.Admin.Config
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
...@@ -25,18 +26,21 @@ import Gargantext.Prelude ...@@ -25,18 +26,21 @@ import Gargantext.Prelude
findListsId :: (HasNodeError err, HasTreeError err) findListsId :: (HasNodeError err, HasTreeError err)
=> User -> NodeMode -> Cmd err [NodeId] => User -> NodeMode -> Cmd err [NodeId]
findListsId u mode = do findListsId u mode = do
r <- getRootId u rootId <- getRootId u
ns <- map _dt_nodeId <$> filter (\n -> _dt_typeId n == nodeTypeId NodeList) ns <- map (view dt_nodeId) <$> filter ((== nodeTypeId NodeList) . (view dt_typeId))
<$> findNodes' mode r <$> findNodes' rootId mode
pure ns pure ns
-- | TODO not clear enough:
-- | Shared is for Shared with me but I am not the owner of it
-- | Private is for all Lists I have created
findNodes' :: HasTreeError err findNodes' :: HasTreeError err
=> NodeMode -> RootId => RootId
-> NodeMode
-> Cmd err [DbTreeNode] -> Cmd err [DbTreeNode]
findNodes' Private r = findNodes Private r $ [NodeFolderPrivate] <> commonNodes findNodes' r Private = findNodes r Private $ [NodeFolderPrivate] <> commonNodes
findNodes' Shared r = findNodes Shared r $ [NodeFolderShared ] <> commonNodes findNodes' r Shared = findNodes r Shared $ [NodeFolderShared, NodeTeam] <> commonNodes
findNodes' Public r = findNodes Public r $ [NodeFolderPublic ] <> commonNodes findNodes' r Public = findNodes r Public $ [NodeFolderPublic ] <> commonNodes
commonNodes:: [NodeType] commonNodes:: [NodeType]
commonNodes = [NodeFolder, NodeCorpus, NodeList] commonNodes = [NodeFolder, NodeCorpus, NodeList, NodeFolderShared, NodeTeam]
{-|
Module : Gargantext.Core.Text.List.Social.ListType
Description :
Copyright : (c) CNRS, 2018-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.Core.Text.List.Social.ListType
where
import Gargantext.Database.Admin.Types.Node
import Data.Map (Map)
import Data.Set (Set)
import Data.Text (Text)
import Gargantext.Prelude
import Gargantext.API.Ngrams.Tools -- (getListNgrams)
import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types.Main
import Gargantext.Database.Schema.Ngrams
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Set as Set
------------------------------------------------------------------------
-- | [ListId] does not merge the lists (it is for Master and User lists
-- here we need UserList only
countFilterList :: RepoCmdM env err m
=> Set Text -> NgramsType -> [ListId]
-> Map Text (Map ListType Int)
-> m (Map Text (Map ListType Int))
countFilterList st nt ls input =
foldM' (\m l -> countFilterList' st nt [l] m) input ls
where
countFilterList' :: RepoCmdM env err m
=> Set Text -> NgramsType -> [ListId]
-> Map Text (Map ListType Int)
-> m (Map Text (Map ListType Int))
countFilterList' st' nt' ls' input' = do
ml <- toMapTextListType <$> getListNgrams ls' nt'
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 m = Map.fromListWith (<>)
$ List.concat
$ map (toList m)
$ Map.toList m
where
toList :: Map Text NgramsRepoElement -> (Text, NgramsRepoElement) -> [(Text, ListType)]
toList m' (t, nre@(NgramsRepoElement _ _ _ _ (MSet children))) =
List.zip terms (List.cycle [lt'])
where
terms = [t]
-- <> maybe [] (\n -> [unNgramsTerm n]) root
-- <> maybe [] (\n -> [unNgramsTerm n]) parent
<> (map unNgramsTerm $ Map.keys children)
lt' = listOf m' nre
listOf :: Map Text NgramsRepoElement -> NgramsRepoElement -> ListType
listOf m'' ng = case _nre_parent ng of
Nothing -> _nre_list ng
Just p -> case Map.lookup (unNgramsTerm p) m'' of
Just ng' -> listOf m'' ng'
Nothing -> CandidateTerm
-- panic "[G.C.T.L.Social.listOf] Nothing: Should Not happen"
------------------------------------------------------------------------
countList :: Text
-> Map Text ListType
-> Map Text (Map ListType Int)
-> Map Text (Map ListType Int)
countList t m input = case Map.lookup t m of
Nothing -> input
Just l -> Map.alter addList t input
where
addList Nothing = Just $ addCountList l Map.empty
addList (Just lm) = Just $ addCountList l lm
addCountList :: ListType -> Map ListType Int -> Map ListType Int
addCountList l' m' = Map.alter (plus l') l' m'
where
plus CandidateTerm Nothing = Just 1
plus CandidateTerm (Just x) = Just $ x + 1
plus MapTerm Nothing = Just 2
plus MapTerm (Just x) = Just $ x + 2
plus StopTerm Nothing = Just 3
plus StopTerm (Just x) = Just $ x + 3
{-|
Module : Gargantext.Core.Text.List.Social.Prelude
Description :
Copyright : (c) CNRS, 2018-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
------------------------------------------------------------------------
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
------------------------------------------------------------------------
module Gargantext.Core.Text.List.Social.Prelude
where
import Control.Lens
import Data.Semigroup (Semigroup(..))
import Data.Monoid
import Data.Map (Map)
import Data.Text (Text)
import Gargantext.Core.Types.Main
import Gargantext.Prelude
import GHC.Generics (Generic)
import qualified Data.Map as Map
------------------------------------------------------------------------
type Parent = Text
------------------------------------------------------------------------
-- | DataType inspired by continuation Monad (but simpler)
data FlowCont a b =
FlowCont { _flc_scores :: Map a b
, _flc_cont :: Map a b
}
instance (Ord a, Eq b) => Monoid (FlowCont a b) where
mempty = FlowCont mempty mempty
instance (Eq a, Ord a, Eq b) => Semigroup (FlowCont a b) where
(<>) (FlowCont m1 s1)
(FlowCont m2 s2)
= FlowCont (m1 <> m2)
(s1 <> s2)
makeLenses ''FlowCont
-- | Datatype definition
data FlowListScores =
FlowListScores { _fls_listType :: Map ListType Int
, _fls_parents :: Map Parent Int
-- You can add any score by incrementing this type
-- , _flc_score :: Map Score Int
}
deriving (Show, Generic, Eq)
makeLenses ''FlowListScores
-- | Rules to compose 2 datatype FlowListScores
-- About the shape of the Type fun:
-- Triangle de Pascal, nombre d'or ou pi ?
-- Question: how to add a score field and derive such definition
-- without the need to fix it below ?
instance Semigroup FlowListScores where
(<>) (FlowListScores p1 l1)
(FlowListScores p2 l2) =
FlowListScores (p1 <> p2)
(l1 <> l2)
instance Monoid FlowListScores where
mempty = FlowListScores Map.empty Map.empty
------------------------------------------------------------------------
-- | Tools to inherit groupings
------------------------------------------------------------------------
-- | Tools
parentUnionsMerge :: (Ord a, Ord b, Num c)
=> [Map a (Map b c)]
-> Map a (Map b c)
parentUnionsMerge = Map.unionsWith (Map.unionWith (+))
-- This Parent union is specific
-- [Private, Shared, Public]
-- means the following preferences:
-- Private > Shared > Public
-- if data have not been tagged privately, then use others tags
-- This unions behavior takes first key only and ignore others
parentUnionsExcl :: Ord a
=> [Map a b]
-> Map a b
parentUnionsExcl = Map.unions
------------------------------------------------------------------------
hasParent :: Text
-> Map Text (Map Parent Int)
-> Maybe Parent
hasParent t m = case Map.lookup t m of
Nothing -> Nothing
Just m' -> keyWithMaxValue m'
------------------------------------------------------------------------
keyWithMaxValue :: Map a b -> Maybe a
keyWithMaxValue m = (fst . fst) <$> Map.maxViewWithKey m
...@@ -14,103 +14,78 @@ Portability : POSIX ...@@ -14,103 +14,78 @@ Portability : POSIX
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
module Gargantext.Core.Text.List.Social.Scores module Gargantext.Core.Text.List.Social.Scores
where where
import Control.Lens import Control.Lens
import Data.Map (Map) import Data.Map (Map)
import Data.Semigroup (Semigroup(..)) import Data.Monoid (mempty)
import Data.Set (Set) import Data.Set (Set)
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Core.Text.List.Social.Prelude
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set import qualified Data.Set as Set
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Tools to inherit groupings -- | Generates Score from list of Map Text NgramsRepoElement
------------------------------------------------------------------------
-- | Tools
parentUnionsMerge :: (Ord a, Ord b, Num c)
=> [Map a (Map b c)]
-> Map a (Map b c)
parentUnionsMerge = Map.unionsWith (Map.unionWith (+))
-- This Parent union is specific
-- [Private, Shared, Public]
-- means the following preferences:
-- Private > Shared > Public
-- if data have not been tagged privately, then use others tags
-- This unions behavior takes first key only and ignore others
parentUnionsExcl :: Ord a
=> [Map a b]
-> Map a b
parentUnionsExcl = Map.unions
------------------------------------------------------------------------
type Parent = Text
hasParent :: Text
-> Map Text (Map Parent Int)
-> Maybe Parent
hasParent t m = case Map.lookup t m of
Nothing -> Nothing
Just m' -> keyWithMaxValue m'
------------------------------------------------------------------------
keyWithMaxValue :: Map a b -> Maybe a
keyWithMaxValue m = (fst . fst) <$> Map.maxViewWithKey m
------------------------------------------------------------------------
data FlowListScores =
FlowListScores { _fls_parents :: Map Parent Int
, _fls_listType :: Map ListType Int
-- You can add any score by incrementing this type
-- , _flc_score :: Map Score Int
}
deriving (Show, Generic)
makeLenses ''FlowListScores
instance Semigroup FlowListScores where
(<>) (FlowListScores p1 l1) (FlowListScores p2 l2) =
FlowListScores (p1 <> p2) (l1 <> l2)
------------------------------------------------------------------------
------------------------------------------------------------------------
-- | toFlowListScores which generate Score from list of Map Text
-- NgramsRepoElement
toFlowListScores :: KeepAllParents toFlowListScores :: KeepAllParents
-> Set Text -> FlowCont Text FlowListScores
-> Map Text FlowListScores
-> [Map Text NgramsRepoElement] -> [Map Text NgramsRepoElement]
-> Map Text FlowListScores -> FlowCont Text FlowListScores
toFlowListScores k ts = foldl' (toFlowListScores' k ts) toFlowListScores k flc_origin = foldl' (toFlowListScores_Level1 k flc_origin) mempty
where where
toFlowListScores' :: KeepAllParents toFlowListScores_Level1 :: KeepAllParents
-> Set Text -> FlowCont Text FlowListScores
-> Map Text FlowListScores -> FlowCont Text FlowListScores
-> Map Text NgramsRepoElement -> Map Text NgramsRepoElement
-> Map Text FlowListScores -> FlowCont Text FlowListScores
toFlowListScores' k' ts' to' ngramsRepo = toFlowListScores_Level1 k' flc_origin' flc_dest ngramsRepo =
Set.foldl' (toFlowListScores'' k' ts' ngramsRepo) to' ts' Set.foldl' (toFlowListScores_Level2 k' ngramsRepo flc_origin')
flc_dest
toFlowListScores'' :: KeepAllParents (Set.fromList $ Map.keys $ view flc_cont flc_origin')
-> Set Text
-> Map Text NgramsRepoElement toFlowListScores_Level2 :: KeepAllParents
-> Map Text FlowListScores -> Map Text NgramsRepoElement
-> Text -> FlowCont Text FlowListScores
-> Map Text FlowListScores -> FlowCont Text FlowListScores
toFlowListScores'' k'' ss ngramsRepo to'' t = -> Text
-> FlowCont Text FlowListScores
toFlowListScores_Level2 k'' ngramsRepo flc_origin'' flc_dest' t =
case Map.lookup t ngramsRepo of case Map.lookup t ngramsRepo of
Nothing -> to'' Nothing -> over flc_cont (Map.union $ Map.singleton t mempty) flc_dest'
Just nre -> Map.alter (addParent k'' nre ss) t Just nre -> updateScoresParent k'' ngramsRepo nre flc_origin''
$ Map.alter (addList $ _nre_list nre) t to'' $ updateScores k'' t nre setText flc_dest'
where
setText = Set.fromList
$ Map.keys
$ view flc_cont flc_origin''
updateScoresParent :: KeepAllParents -> Map Text NgramsRepoElement -> NgramsRepoElement
-> FlowCont Text FlowListScores
-> FlowCont Text FlowListScores
-> FlowCont Text FlowListScores
updateScoresParent keep@(KeepAllParents k''') ngramsRepo nre flc_origin'' flc_dest'' = case k''' of
False -> flc_dest''
True -> case view nre_parent nre of
Nothing -> flc_dest''
Just (NgramsTerm parent) -> toFlowListScores_Level2 keep ngramsRepo flc_origin'' flc_dest'' parent
------------------------------------------------------------------------
updateScores :: KeepAllParents
-> Text -> NgramsRepoElement -> Set Text
-> FlowCont Text FlowListScores
-> FlowCont Text FlowListScores
updateScores k t nre setText mtf =
over flc_cont ( Map.delete t)
$ over flc_scores ((Map.alter (addParent k nre setText ) t)
.(Map.alter (addList $ view nre_list nre) t)
) mtf
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Main addFunctions to groupResolution the FlowListScores -- | Main addFunctions to groupResolution the FlowListScores
...@@ -120,18 +95,17 @@ addList :: ListType ...@@ -120,18 +95,17 @@ addList :: ListType
-> Maybe FlowListScores -> Maybe FlowListScores
-> Maybe FlowListScores -> Maybe FlowListScores
addList l Nothing = addList l Nothing =
Just $ FlowListScores Map.empty (addList' l Map.empty) Just $ set fls_listType (addListScore l mempty) mempty
addList l (Just fls) =
Just $ over fls_listType (addListScore l) fls
addList l (Just (FlowListScores mapParent mapList)) =
Just $ FlowListScores mapParent mapList'
where
mapList' = addList' l mapList
-- * Unseful but nice comment: -- * Unseful but nice comment:
-- "the addList function looks like an ASCII bird" -- "the addList function looks like an ASCII bird"
-- | Concrete function to pass to PatchMap -- | Concrete function to pass to PatchMap
addList' :: ListType -> Map ListType Int -> Map ListType Int addListScore :: ListType -> Map ListType Int -> Map ListType Int
addList' l m = Map.alter (plus l) l m addListScore l m = Map.alter (plus l) l m
where where
plus CandidateTerm Nothing = Just 1 plus CandidateTerm Nothing = Just 1
plus CandidateTerm (Just x) = Just $ x + 1 plus CandidateTerm (Just x) = Just $ x + 1
...@@ -142,7 +116,6 @@ addList' l m = Map.alter (plus l) l m ...@@ -142,7 +116,6 @@ addList' l m = Map.alter (plus l) l m
plus StopTerm Nothing = Just 3 plus StopTerm Nothing = Just 3
plus StopTerm (Just x) = Just $ x + 3 plus StopTerm (Just x) = Just $ x + 3
------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
data KeepAllParents = KeepAllParents Bool data KeepAllParents = KeepAllParents Bool
...@@ -151,24 +124,22 @@ addParent :: KeepAllParents -> NgramsRepoElement -> Set Text ...@@ -151,24 +124,22 @@ addParent :: KeepAllParents -> NgramsRepoElement -> Set Text
-> Maybe FlowListScores -> Maybe FlowListScores
addParent k nre ss Nothing = addParent k nre ss Nothing =
Just $ FlowListScores mapParent Map.empty Just $ FlowListScores mempty mapParent
where where
mapParent = addParent' k (_nre_parent nre) ss Map.empty mapParent = addParentScore k (view nre_parent nre) ss mempty
addParent k nre ss (Just (FlowListScores mapParent mapList)) = addParent k nre ss (Just fls{-(FlowListScores mapList mapParent)-}) =
Just $ FlowListScores mapParent' mapList Just $ over fls_parents (addParentScore k (view nre_parent nre) ss) fls
where
mapParent' = addParent' k (_nre_parent nre) ss mapParent
addParent' :: Num a addParentScore :: Num a
=> KeepAllParents => KeepAllParents
-> Maybe NgramsTerm -> Maybe NgramsTerm
-> Set Text -> Set Text
-> Map Text a -> Map Text a
-> Map Text a -> Map Text a
addParent' _ Nothing _ss mapParent = mapParent addParentScore _ Nothing _ss mapParent = mapParent
addParent' (KeepAllParents k) (Just (NgramsTerm p')) ss mapParent = addParentScore (KeepAllParents keep) (Just (NgramsTerm p')) ss mapParent =
case k of case keep of
True -> Map.alter addCount p' mapParent True -> Map.alter addCount p' mapParent
False -> case Set.member p' ss of False -> case Set.member p' ss of
False -> mapParent False -> mapParent
...@@ -178,3 +149,4 @@ addParent' (KeepAllParents k) (Just (NgramsTerm p')) ss mapParent = ...@@ -178,3 +149,4 @@ addParent' (KeepAllParents k) (Just (NgramsTerm p')) ss mapParent =
addCount (Just n) = Just $ n + 1 addCount (Just n) = Just $ n + 1
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------
...@@ -11,14 +11,17 @@ Mainly reexport functions in @Data.Text.Metrics@ ...@@ -11,14 +11,17 @@ Mainly reexport functions in @Data.Text.Metrics@
-} -}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.Core.Text.Metrics module Gargantext.Core.Text.Metrics
where where
--import Data.Array.Accelerate ((:.)(..), Z(..)) --import Data.Array.Accelerate ((:.)(..), Z(..))
--import Math.KMeans (kmeans, euclidSq, elements) --import Math.KMeans (kmeans, euclidSq, elements)
import Control.Lens (makeLenses)
import Data.Map (Map) import Data.Map (Map)
import Data.Semigroup (Semigroup)
import Data.Monoid (Monoid, mempty)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Methods.Distances.Accelerate.SpeGen import Gargantext.Core.Methods.Distances.Accelerate.SpeGen
import Gargantext.Core.Viz.Graph.Index import Gargantext.Core.Viz.Graph.Index
...@@ -46,8 +49,17 @@ data Scored ts = Scored ...@@ -46,8 +49,17 @@ data Scored ts = Scored
{ _scored_terms :: !ts { _scored_terms :: !ts
, _scored_genInc :: !GenericityInclusion , _scored_genInc :: !GenericityInclusion
, _scored_speExc :: !SpecificityExclusion , _scored_speExc :: !SpecificityExclusion
} deriving (Show) } deriving (Show, Eq, Ord)
instance Monoid a => Monoid (Scored a) where
mempty = Scored mempty mempty mempty
instance Semigroup a => Semigroup (Scored a) where
(<>) (Scored a b c )
(Scored _a' b' c')
= Scored (a {-<> a'-})
(b <> b')
(c <> c')
localMetrics' :: Ord t => Map (t,t) Int -> Map t (Vec.Vector Double) localMetrics' :: Ord t => Map (t,t) Int -> Map t (Vec.Vector Double)
localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [inc,spe])) localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [inc,spe]))
...@@ -96,5 +108,5 @@ normalizeLocal (Scored t s1 s2) = Scored t (log' 5 s1) (log' 2 s2) ...@@ -96,5 +108,5 @@ normalizeLocal (Scored t s1 s2) = Scored t (log' 5 s1) (log' 2 s2)
-- | Type Instances
makeLenses 'Scored
...@@ -31,7 +31,7 @@ import Gargantext.Prelude ...@@ -31,7 +31,7 @@ import Gargantext.Prelude
import Gargantext.Core.Text.Metrics.Count (occurrencesWith) import Gargantext.Core.Text.Metrics.Count (occurrencesWith)
-- Pie Chart -- Pie Chart
import Gargantext.API.Ngrams.NTree import Gargantext.API.Ngrams.NgramsTree
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Database.Action.Flow import Gargantext.Database.Action.Flow
...@@ -71,7 +71,7 @@ chartData cId nt lt = do ...@@ -71,7 +71,7 @@ chartData cId nt lt = do
treeData :: FlowCmdM env err m treeData :: FlowCmdM env err m
=> CorpusId -> NgramsType -> ListType => CorpusId -> NgramsType -> ListType
-> m [MyTree] -> m [NgramsTree]
treeData cId nt lt = do treeData cId nt lt = do
ls' <- selectNodesWithUsername NodeList userMaster ls' <- selectNodesWithUsername NodeList userMaster
ls <- map (_node_id) <$> getListsWithParentId cId ls <- map (_node_id) <$> getListsWithParentId cId
......
...@@ -27,7 +27,7 @@ import Control.Applicative ...@@ -27,7 +27,7 @@ import Control.Applicative
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Viz.Types (Histo(..)) import Gargantext.Core.Viz.Types (Histo(..))
import Gargantext.API.Ngrams.NTree (MyTree) import Gargantext.API.Ngrams.NgramsTree (NgramsTree)
import Gargantext.API.Ngrams.Types (TabType) import Gargantext.API.Ngrams.Types (TabType)
import Gargantext.Database.Admin.Types.Hyperdata.Prelude import Gargantext.Database.Admin.Types.Hyperdata.Prelude
import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metrics) import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metrics)
...@@ -38,13 +38,13 @@ data HyperdataList = ...@@ -38,13 +38,13 @@ data HyperdataList =
, _hl_list :: !(Maybe Text) , _hl_list :: !(Maybe Text)
, _hl_pie :: !(Map TabType (ChartMetrics Histo)) , _hl_pie :: !(Map TabType (ChartMetrics Histo))
, _hl_scatter :: !(Map TabType Metrics) , _hl_scatter :: !(Map TabType Metrics)
, _hl_tree :: !(Map TabType (ChartMetrics [MyTree])) , _hl_tree :: !(Map TabType (ChartMetrics [NgramsTree]))
} deriving (Show, Generic) } deriving (Show, Generic)
-- HyperdataList { _hl_chart :: !(Maybe (ChartMetrics Histo)) -- HyperdataList { _hl_chart :: !(Maybe (ChartMetrics Histo))
-- , _hl_list :: !(Maybe Text) -- , _hl_list :: !(Maybe Text)
-- , _hl_pie :: !(Maybe (ChartMetrics Histo)) -- , _hl_pie :: !(Maybe (ChartMetrics Histo))
-- , _hl_scatter :: !(Maybe Metrics) -- , _hl_scatter :: !(Maybe Metrics)
-- , _hl_tree :: !(Maybe (ChartMetrics [MyTree])) -- , _hl_tree :: !(Maybe (ChartMetrics [NgramsTree]))
-- } deriving (Show, Generic) -- } deriving (Show, Generic)
defaultHyperdataList :: HyperdataList defaultHyperdataList :: HyperdataList
......
...@@ -34,7 +34,7 @@ module Gargantext.Database.Query.Tree ...@@ -34,7 +34,7 @@ module Gargantext.Database.Query.Tree
) )
where where
import Control.Lens ((^..), at, each, _Just, to, set, makeLenses) import Control.Lens (view, toListOf, at, each, _Just, to, set, makeLenses)
import Control.Monad.Error.Class (MonadError()) import Control.Monad.Error.Class (MonadError())
import Data.List (tail, concat, nub) import Data.List (tail, concat, nub)
import Data.Map (Map, fromListWith, lookup) import Data.Map (Map, fromListWith, lookup)
...@@ -93,22 +93,22 @@ tree_advanced :: HasTreeError err ...@@ -93,22 +93,22 @@ tree_advanced :: HasTreeError err
-> [NodeType] -> [NodeType]
-> Cmd err (Tree NodeTree) -> Cmd err (Tree NodeTree)
tree_advanced r nodeTypes = do tree_advanced r nodeTypes = do
mainRoot <- findNodes Private r nodeTypes mainRoot <- findNodes r Private nodeTypes
sharedRoots <- findNodes Shared r nodeTypes sharedRoots <- findNodes r Shared nodeTypes
publicRoots <- findNodes Public r nodeTypes publicRoots <- findNodes r Public nodeTypes
toTree $ toTreeParent (mainRoot <> sharedRoots <> publicRoots) toTree $ toTreeParent (mainRoot <> sharedRoots <> publicRoots)
------------------------------------------------------------------------ ------------------------------------------------------------------------
data NodeMode = Private | Shared | Public data NodeMode = Private | Shared | Public
findNodes :: HasTreeError err findNodes :: HasTreeError err
=> NodeMode => RootId
-> RootId -> [NodeType] -> NodeMode
-> [NodeType]
-> Cmd err [DbTreeNode] -> Cmd err [DbTreeNode]
findNodes Private r nt = dbTree r nt findNodes r Private nt = dbTree r nt
findNodes Shared r nt = findShared r NodeFolderShared nt sharedTreeUpdate findNodes r Shared nt = findShared r NodeFolderShared nt sharedTreeUpdate
findNodes Public r nt = findShared r NodeFolderPublic nt publicTreeUpdate findNodes r Public nt = findShared r NodeFolderPublic nt publicTreeUpdate
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Collaborative Nodes in the Tree -- | Collaborative Nodes in the Tree
...@@ -120,6 +120,7 @@ findShared r nt nts fun = do ...@@ -120,6 +120,7 @@ findShared r nt nts fun = do
trees <- mapM (updateTree nts fun) foldersSharedId trees <- mapM (updateTree nts fun) foldersSharedId
pure $ concat trees pure $ concat trees
type UpdateTree err = ParentId -> [NodeType] -> NodeId -> Cmd err [DbTreeNode] type UpdateTree err = ParentId -> [NodeType] -> NodeId -> Cmd err [DbTreeNode]
updateTree :: HasTreeError err updateTree :: HasTreeError err
...@@ -134,7 +135,7 @@ updateTree nts fun r = do ...@@ -134,7 +135,7 @@ updateTree nts fun r = do
sharedTreeUpdate :: HasTreeError err => UpdateTree err sharedTreeUpdate :: HasTreeError err => UpdateTree err
sharedTreeUpdate p nt n = dbTree n nt sharedTreeUpdate p nt n = dbTree n nt
<&> map (\n' -> if _dt_nodeId n' == n <&> map (\n' -> if (view dt_nodeId n') == n
-- && elem (fromNodeTypeId $ _dt_typeId n') [NodeGraph] -- && elem (fromNodeTypeId $ _dt_typeId n') [NodeGraph]
-- && not (elem (fromNodeTypeId $ _dt_typeId n') [NodeFile]) -- && not (elem (fromNodeTypeId $ _dt_typeId n') [NodeFile])
then set dt_parentId (Just p) n' then set dt_parentId (Just p) n'
...@@ -174,13 +175,14 @@ toTree m = ...@@ -174,13 +175,14 @@ toTree m =
-> Tree NodeTree -> Tree NodeTree
toTree' m' n = toTree' m' n =
TreeN (toNodeTree n) $ TreeN (toNodeTree n) $
m' ^.. at (Just $ _dt_nodeId n) . _Just . each . to (toTree' m') -- | Lines below are equivalent computationally but not semantically
-- m' ^.. at (Just $ _dt_nodeId n) . _Just . each . to (toTree' m')
toListOf (at (Just $ _dt_nodeId n) . _Just . each . to (toTree' m')) m'
toNodeTree :: DbTreeNode toNodeTree :: DbTreeNode
-> NodeTree -> NodeTree
toNodeTree (DbTreeNode nId tId _ n) = NodeTree n nodeType nId toNodeTree (DbTreeNode nId tId _ n) = NodeTree n (fromNodeTypeId tId) nId
where
nodeType = fromNodeTypeId tId
------------------------------------------------------------------------ ------------------------------------------------------------------------
toTreeParent :: [DbTreeNode] toTreeParent :: [DbTreeNode]
-> Map (Maybe ParentId) [DbTreeNode] -> Map (Maybe ParentId) [DbTreeNode]
......
...@@ -10,6 +10,7 @@ Portability : POSIX ...@@ -10,6 +10,7 @@ Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Gargantext.Prelude module Gargantext.Prelude
...@@ -35,6 +36,8 @@ import GHC.Err.Located (undefined) ...@@ -35,6 +36,8 @@ import GHC.Err.Located (undefined)
import GHC.Real (round) import GHC.Real (round)
import Data.Map (Map, lookup) import Data.Map (Map, lookup)
import Data.Maybe (isJust, fromJust, maybe) import Data.Maybe (isJust, fromJust, maybe)
import Data.Monoid (Monoid, mempty)
import Data.Semigroup (Semigroup, (<>))
import Data.Text (Text) import Data.Text (Text)
import Data.Typeable (Typeable) import Data.Typeable (Typeable)
import Protolude ( Bool(True, False), Int, Int64, Double, Integer import Protolude ( Bool(True, False), Int, Int64, Double, Integer
...@@ -306,12 +309,31 @@ lookup2 a b m = do ...@@ -306,12 +309,31 @@ lookup2 a b m = do
m' <- lookup a m m' <- lookup a m
lookup b m' lookup b m'
----------------------------------------------- -----------------------------------------------------------------------
foldM' :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a foldM' :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
foldM' _ z [] = return z foldM' _ z [] = return z
foldM' f z (x:xs) = do foldM' f z (x:xs) = do
z' <- f z x z' <- f z x
z' `seq` foldM' f z' xs z' `seq` foldM' f z' xs
-----------------------------------------------------------------------
-- | Instance for basic numerals
-- See the difference between Double and (Int Or Integer)
instance Monoid Double where
mempty = 1
instance Semigroup Double where
(<>) a b = a * b
-----------
instance Monoid Int where
mempty = 0
instance Semigroup Int where
(<>) a b = a + b
----
instance Monoid Integer where
mempty = 0
instance Semigroup Integer where
(<>) a b = a + b
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