Commit c02e87d8 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into dev-doc-table-score

parents 2a9bc706 77e4ab25
...@@ -29,7 +29,6 @@ import Gargantext.API.Prelude (GargError) ...@@ -29,7 +29,6 @@ import Gargantext.API.Prelude (GargError)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpusFile, flowAnnuaire, TermType(..)) import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpusFile, flowAnnuaire, TermType(..))
import Gargantext.Database.Query.Table.User (insertUsersDemo)
import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument) import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument)
import Gargantext.Database.Admin.Types.Node (CorpusId) import Gargantext.Database.Admin.Types.Node (CorpusId)
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
...@@ -42,9 +41,6 @@ main = do ...@@ -42,9 +41,6 @@ main = do
--{- --{-
let createUsers :: Cmd GargError Int64
createUsers = insertUsersDemo
let let
--tt = (Unsupervised EN 6 0 Nothing) --tt = (Unsupervised EN 6 0 Nothing)
tt = (Multi EN) tt = (Multi EN)
...@@ -70,10 +66,6 @@ main = do ...@@ -70,10 +66,6 @@ main = do
--} --}
withDevEnv iniPath $ \env -> do withDevEnv iniPath $ \env -> do
_ <- if fun == "users"
then runCmdDev env createUsers
else pure 0 --(cs "false")
_ <- if fun == "corpus" _ <- if fun == "corpus"
then runCmdDev env corpus then runCmdDev env corpus
else pure 0 --(cs "false") else pure 0 --(cs "false")
......
...@@ -20,10 +20,10 @@ import Data.Either (Either(..)) ...@@ -20,10 +20,10 @@ import Data.Either (Either(..))
import Gargantext.API.Dev (withDevEnv, runCmdDev) import Gargantext.API.Dev (withDevEnv, runCmdDev)
import Gargantext.API.Prelude (GargError) import Gargantext.API.Prelude (GargError)
import Gargantext.API.Node () -- instances only import Gargantext.API.Node () -- instances only
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..), arbitraryNewUsers, NewUser(..), arbitraryUsername, GargPassword(..))
import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMk_RootWithCorpus) import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMk_RootWithCorpus)
import Gargantext.Database.Query.Table.Node (getOrMkList) import Gargantext.Database.Query.Table.Node (getOrMkList)
import Gargantext.Database.Query.Table.User (insertUsersDemo) import Gargantext.Database.Query.Table.User (insertNewUsers, )
import Gargantext.Database.Admin.Config (userMaster, corpusMasterName) import Gargantext.Database.Admin.Config (userMaster, corpusMasterName)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Trigger.Init (initFirstTriggers, initLastTriggers) import Gargantext.Database.Admin.Trigger.Init (initFirstTriggers, initLastTriggers)
...@@ -31,6 +31,7 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataCorpus) ...@@ -31,6 +31,7 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataCorpus)
import Gargantext.Database.Prelude (Cmd, ) import Gargantext.Database.Prelude (Cmd, )
import Gargantext.Prelude import Gargantext.Prelude
import System.Environment (getArgs) import System.Environment (getArgs)
import Prelude (getLine)
-- TODO put this in gargantext.ini -- TODO put this in gargantext.ini
secret :: Text secret :: Text
...@@ -40,12 +41,21 @@ main :: IO () ...@@ -40,12 +41,21 @@ main :: IO ()
main = do main = do
[iniPath] <- getArgs [iniPath] <- getArgs
putStrLn "Enter master user (gargantua) _password_ :"
password <- getLine
putStrLn "Enter master user (gargantua) _email_ :"
email <- getLine
let createUsers :: Cmd GargError Int64 let createUsers :: Cmd GargError Int64
createUsers = insertUsersDemo createUsers = insertNewUsers (NewUser "gargantua" (cs email) (GargPassword $ cs password)
: arbitraryNewUsers
)
let let
mkRoots :: Cmd GargError [(UserId, RootId)] mkRoots :: Cmd GargError [(UserId, RootId)]
mkRoots = mapM getOrMkRoot $ map UserName ["gargantua", "user1", "user2", "user3"] mkRoots = mapM getOrMkRoot $ map UserName ("gargantua" : arbitraryUsername)
-- TODO create all users roots -- TODO create all users roots
let let
......
name: gargantext name: gargantext
version: '0.0.1.94.1' version: '0.0.2.0'
synopsis: Search, map, share synopsis: Search, map, share
description: Please see README.md description: Please see README.md
category: Data category: Data
......
...@@ -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
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -708,6 +708,8 @@ instance HasRepoSaver RepoEnv where ...@@ -708,6 +708,8 @@ instance HasRepoSaver RepoEnv where
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
) )
......
...@@ -213,7 +213,7 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode ...@@ -213,7 +213,7 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode
:<|> catApi id' :<|> catApi id'
:<|> Search.api id' :<|> Search.api id'
:<|> Share.api id' :<|> Share.api (RootId $ NodeId uId) id'
-- Pairing Tools -- Pairing Tools
:<|> pairWith id' :<|> pairWith id'
:<|> pairs id' :<|> pairs id'
......
...@@ -19,18 +19,21 @@ import Data.Aeson ...@@ -19,18 +19,21 @@ import Data.Aeson
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..), arbitraryUsername)
import Gargantext.Database.Action.Share (ShareNodeWith(..)) import Gargantext.Database.Action.Share (ShareNodeWith(..))
import Gargantext.Database.Action.Share as DB (shareNodeWith, unPublish) import Gargantext.Database.Action.Share as DB (shareNodeWith, unPublish)
import Gargantext.Database.Action.User
import Gargantext.Database.Action.User.New
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Tree (findNodesId)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..)) import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
import Gargantext.Prelude import Gargantext.Prelude
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import qualified Data.List as List
------------------------------------------------------------------------ ------------------------------------------------------------------------
data ShareNodeParams = ShareTeamParams { username :: Text } data ShareNodeParams = ShareTeamParams { username :: Text }
...@@ -49,13 +52,43 @@ instance Arbitrary ShareNodeParams where ...@@ -49,13 +52,43 @@ instance Arbitrary ShareNodeParams where
] ]
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO permission -- TODO permission
-- TODO refactor userId which is used twice
-- TODO change return type for better warning/info/success/error handling on the front
api :: HasNodeError err api :: HasNodeError err
=> NodeId => User
-> NodeId
-> ShareNodeParams -> ShareNodeParams
-> Cmd err Int -> CmdR err Int
api nId (ShareTeamParams user) = api userInviting nId (ShareTeamParams user') = do
user <- case guessUserName user' of
Nothing -> pure user'
Just (u,_) -> do
isRegistered <- getUserId' (UserName u)
case isRegistered of
Just _ -> do
printDebug "[G.A.N.Share.api]" ("Team shared with " <> u)
pure u
Nothing -> do
username' <- getUsername userInviting
_ <- case List.elem username' arbitraryUsername of
True -> do
printDebug "[G.A.N.Share.api]" ("demo users are not allowed to invite" :: Text)
pure ()
False -> do
children <- findNodesId nId [NodeCorpus]
_ <- case List.null children of
True -> do
printDebug "[G.A.N.Share.api]" ("Invitation is enabled if you share a corpus at least" :: Text)
pure 0
False -> do
printDebug "[G.A.N.Share.api]" ("Your invitation is sent to: " <> user')
newUsers [user']
pure ()
pure u
fromIntegral <$> DB.shareNodeWith (ShareNodeWith_User NodeFolderShared (UserName user)) nId fromIntegral <$> DB.shareNodeWith (ShareNodeWith_User NodeFolderShared (UserName user)) nId
api nId2 (SharePublicParams nId1) = api _uId nId2 (SharePublicParams nId1) =
fromIntegral <$> DB.shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId1) nId2 fromIntegral <$> DB.shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId1) nId2
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -68,7 +68,7 @@ type ErrC err = ...@@ -68,7 +68,7 @@ type ErrC err =
) )
type GargServerC env err m = type GargServerC env err m =
( CmdM' env err m ( CmdRandom env err m
, EnvC env , EnvC env
, ErrC err , ErrC err
) )
......
...@@ -15,38 +15,46 @@ Portability : POSIX ...@@ -15,38 +15,46 @@ Portability : POSIX
module Gargantext.Core.Text.List module Gargantext.Core.Text.List
where where
import Control.Lens hiding (both) -- ((^.), view, over, set, (_1), (_2))
import Control.Lens ((^.), set, view)
import Data.Maybe (fromMaybe, catMaybes)
import Data.Ord (Down(..))
import Data.Map (Map) import Data.Map (Map)
import Data.Monoid (mempty)
import Data.Ord (Down(..))
import Data.Set (Set) import Data.Set (Set)
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Char as Char import Data.Tuple.Extra (both)
import qualified Data.List as List import Gargantext.API.Ngrams.Types (NgramsElement)
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Text as Text
-- import Gargantext.API.Ngrams.Tools (getCoocByNgrams', Diagonal(..))
import Gargantext.API.Ngrams.Types (NgramsElement, mkNgramsElement, NgramsTerm(..), RootParent(..), mSetFromList)
import Gargantext.API.Ngrams.Types (RepoCmdM) import Gargantext.API.Ngrams.Types (RepoCmdM)
import Gargantext.Core.Text.List.Social (flowSocialList, flowSocialList', FlowSocialListPriority(..), invertForw) import Gargantext.Core.Text (size)
import Gargantext.Core.Text.List.Social.Scores -- (FlowListScores)
import Gargantext.Core.Text.List.Group import Gargantext.Core.Text.List.Group
import Gargantext.Core.Text.List.Group.Prelude
import Gargantext.Core.Text.List.Group.WithStem import Gargantext.Core.Text.List.Group.WithStem
import Gargantext.Core.Text.Metrics (scored', Scored(..), normalizeGlobal, normalizeLocal) import Gargantext.Core.Text.List.Social
import Gargantext.Core.Text.List.Social.Prelude
import Gargantext.Core.Text.Metrics (scored', Scored(..), scored_speExc, scored_genInc, normalizeGlobal, normalizeLocal, scored_terms)
import Gargantext.Core.Types (ListType(..), MasterCorpusId, UserCorpusId) import Gargantext.Core.Types (ListType(..), MasterCorpusId, UserCorpusId)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsUser, getNodesByNgramsOnlyUser) import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsUser, getNodesByNgramsOnlyUser)
import Gargantext.Database.Action.Metrics.TFICF (getTficf) import Gargantext.Database.Action.Metrics.TFICF (getTficf)
import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Database.Prelude (CmdM) import Gargantext.Database.Prelude (CmdM)
import Gargantext.Database.Query.Table.Node (defaultList) import Gargantext.Database.Query.Table.Node (defaultList)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError()) import Gargantext.Database.Query.Table.Node.Error (HasNodeError())
import Gargantext.Database.Query.Tree.Error (HasTreeError) import Gargantext.Database.Query.Tree.Error (HasTreeError)
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Set as Set
{-
-- TODO maybe useful for later
isStopTerm :: StopSize -> Text -> Bool
isStopTerm (StopSize n) x = Text.length x < n || any isStopChar (Text.unpack x)
where
isStopChar c = not (c `elem` ("- /()%" :: [Char]) || Char.isAlpha c)
-}
-- | TODO improve grouping functions of Authors, Sources, Institutes.. -- | TODO improve grouping functions of Authors, Sources, Institutes..
...@@ -61,8 +69,8 @@ buildNgramsLists :: ( RepoCmdM env err m ...@@ -61,8 +69,8 @@ buildNgramsLists :: ( RepoCmdM env err m
-> MasterCorpusId -> MasterCorpusId
-> m (Map NgramsType [NgramsElement]) -> m (Map NgramsType [NgramsElement])
buildNgramsLists user gp uCid mCid = do buildNgramsLists user gp uCid mCid = do
ngTerms <- buildNgramsTermsList user uCid mCid gp ngTerms <- buildNgramsTermsList user uCid mCid gp (NgramsTerms, MapListSize 350)
othersTerms <- mapM (buildNgramsOthersList user uCid (ngramsGroup GroupIdentity)) othersTerms <- mapM (buildNgramsOthersList user uCid GroupIdentity)
[ (Authors , MapListSize 9) [ (Authors , MapListSize 9)
, (Sources , MapListSize 9) , (Sources , MapListSize 9)
, (Institutes, MapListSize 9) , (Institutes, MapListSize 9)
...@@ -80,39 +88,36 @@ buildNgramsOthersList ::( HasNodeError err ...@@ -80,39 +88,36 @@ buildNgramsOthersList ::( HasNodeError err
) )
=> User => User
-> UserCorpusId -> UserCorpusId
-> (Text -> Text) -> GroupParams
-> (NgramsType, MapListSize) -> (NgramsType, MapListSize)
-> m (Map NgramsType [NgramsElement]) -> m (Map NgramsType [NgramsElement])
buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do buildNgramsOthersList user uCid groupParams (nt, MapListSize mapListSize) = do
ngs' :: Map Text (Set NodeId) <- getNodesByNgramsUser uCid nt allTerms :: Map Text (Set NodeId) <- getNodesByNgramsUser uCid nt
socialLists' :: Map Text FlowListScores -- | PrivateFirst for first developments since Public NodeMode is not implemented yet
<- flowSocialList' MySelfFirst user nt (Set.fromList $ Map.keys ngs') socialLists' :: FlowCont Text FlowListScores
-- PrivateFirst for first developments since Public NodeMode is not implemented yet <- flowSocialList' MySelfFirst user nt ( FlowCont Map.empty
$ Map.fromList
printDebug "flowSocialList'" (Map.filter (not . ((==) Map.empty) . view fls_parents) socialLists') $ List.zip (Map.keys allTerms)
(List.cycle [mempty])
)
let let
groupParams = GroupedTextParams groupIt (Set.size . snd) fst snd {-(size . fst)-} groupedWithList = toGroupedTree groupParams socialLists' allTerms
groupedWithList = toGroupedText groupParams socialLists' ngs'
printDebug "groupedWithList" (Map.map (\v -> (view gt_label v, view gt_children v)) $ Map.filter (\v -> (Set.size $ view gt_children v) > 0) groupedWithList)
let let
(stopTerms, tailTerms) = Map.partition (\t -> t ^. gt_listType == Just StopTerm) groupedWithList (stopTerms, tailTerms) = Map.partition ((== Just StopTerm) . viewListType) $ view flc_scores groupedWithList
(mapTerms, tailTerms') = Map.partition (\t -> t ^. gt_listType == Just MapTerm) tailTerms (mapTerms, tailTerms') = Map.partition ((== Just MapTerm) . viewListType) tailTerms
listSize = mapListSize - (List.length mapTerms) listSize = mapListSize - (List.length mapTerms)
(mapTerms', candiTerms) = List.splitAt listSize (mapTerms', candiTerms) = both Map.fromList
$ List.sortOn (Down . _gt_score) $ List.splitAt listSize
$ Map.elems tailTerms' $ List.sortOn (Down . viewScore . snd)
$ Map.toList tailTerms'
pure $ Map.fromList [( nt, (List.concat $ map toNgramsElement stopTerms)
<> (List.concat $ map toNgramsElement mapTerms ) pure $ Map.fromList [( nt, (toNgramsElement stopTerms)
<> (List.concat $ map toNgramsElement <> (toNgramsElement mapTerms )
$ map (set gt_listType (Just MapTerm )) mapTerms' ) <> (toNgramsElement $ setListType (Just MapTerm ) mapTerms' )
<> (List.concat $ map toNgramsElement <> (toNgramsElement $ setListType (Just CandidateTerm) candiTerms)
$ map (set gt_listType (Just CandidateTerm)) candiTerms)
)] )]
...@@ -126,185 +131,140 @@ buildNgramsTermsList :: ( HasNodeError err ...@@ -126,185 +131,140 @@ buildNgramsTermsList :: ( HasNodeError err
-> UserCorpusId -> UserCorpusId
-> MasterCorpusId -> MasterCorpusId
-> GroupParams -> GroupParams
-> (NgramsType, MapListSize)
-> m (Map NgramsType [NgramsElement]) -> m (Map NgramsType [NgramsElement])
buildNgramsTermsList user uCid mCid groupParams = do buildNgramsTermsList user uCid mCid groupParams (nt, _mapListSize)= do
-- Computing global speGen score
allTerms :: Map Text Double <- getTficf uCid mCid NgramsTerms
-- printDebug "head candidates" (List.take 10 $ allTerms) -- | Filter 0 With Double
-- printDebug "tail candidates" (List.take 10 $ List.reverse $ allTerms)
-- First remove stops terms -- Computing global speGen score
socialLists <- flowSocialList user NgramsTerms (Set.fromList $ map fst $ Map.toList allTerms) allTerms :: Map Text Double <- getTficf uCid mCid nt
-- printDebug "\n * socialLists * \n" socialLists
-- | PrivateFirst for first developments since Public NodeMode is not implemented yet
-- Grouping the ngrams and keeping the maximum score for label socialLists' :: FlowCont Text FlowListScores
let grouped = groupedTextWithStem ( GroupedTextParams (ngramsGroup groupParams) identity (const Set.empty) (const Set.empty) {-(size . _gt_label)-} ) allTerms <- flowSocialList' MySelfFirst user nt ( FlowCont Map.empty
$ Map.fromList
groupedWithList = map (addListType (invertForw socialLists)) grouped $ List.zip (Map.keys allTerms)
(List.cycle [mempty])
(stopTerms, candidateTerms) = Map.partition (\t -> t ^. gt_listType == Just StopTerm) groupedWithList )
(groupedMono, groupedMult) = Map.partition (\t -> t ^. gt_size < 2) candidateTerms let groupedWithList = toGroupedTree groupParams socialLists' allTerms
(stopTerms, candidateTerms) = Map.partition ((== Just StopTerm) . viewListType)
$ view flc_scores groupedWithList
(groupedMono, groupedMult) = Map.partitionWithKey (\t _v -> size t < 2) candidateTerms
-- printDebug "\n * stopTerms * \n" stopTerms
-- splitting monterms and multiterms to take proportional candidates -- splitting monterms and multiterms to take proportional candidates
let let
listSizeGlobal = 2000 :: Double -- use % of list if to big, or Int if too small -- use % of list if to big, or Int if too small
listSizeGlobal = 2000 :: Double
monoSize = 0.4 :: Double monoSize = 0.4 :: Double
multSize = 1 - monoSize multSize = 1 - monoSize
splitAt n' ns = List.splitAt (round $ n' * listSizeGlobal) $ List.sort $ Map.elems ns splitAt n' ns = both (Map.fromListWith (<>))
$ List.splitAt (round $ n' * listSizeGlobal)
$ List.sortOn (viewScore . snd)
$ Map.toList ns
(groupedMonoHead, groupedMonoTail) = splitAt monoSize groupedMono (groupedMonoHead, groupedMonoTail) = splitAt monoSize groupedMono
(groupedMultHead, groupedMultTail) = splitAt multSize groupedMult (groupedMultHead, groupedMultTail) = splitAt multSize groupedMult
-- printDebug "groupedMonoHead" (List.length groupedMonoHead) -------------------------
-- printDebug "groupedMonoTail" (List.length groupedMonoHead) -- Filter 1 With Set NodeId and SpeGen
-- printDebug "groupedMultHead" (List.length groupedMultHead) selectedTerms = Set.toList $ hasTerms (groupedMonoHead <> groupedMultHead)
-- printDebug "groupedMultTail" (List.length groupedMultTail)
let
-- Get Local Scores now for selected grouped ngrams
selectedTerms = Set.toList $ List.foldl'
(\set' (GroupedText _ l' _ g _ _ _ ) -> Set.union set'
$ Set.insert l' g
)
Set.empty
(groupedMonoHead <> groupedMultHead)
-- TO remove (and remove HasNodeError instance) -- TO remove (and remove HasNodeError instance)
userListId <- defaultList uCid userListId <- defaultList uCid
masterListId <- defaultList mCid masterListId <- defaultList mCid
mapTextDocIds <- getNodesByNgramsOnlyUser uCid [userListId, masterListId] NgramsTerms selectedTerms
mapTextDocIds <- getNodesByNgramsOnlyUser uCid
[userListId, masterListId]
nt
selectedTerms
let let
mapGroups = Map.fromList groupedTreeScores_SetNodeId :: Map Text (GroupedTreeScores (Set NodeId))
$ map (\g -> (g ^. gt_stem, g)) groupedTreeScores_SetNodeId = setScoresWithMap mapTextDocIds (groupedMonoHead <> groupedMultHead)
$ groupedMonoHead <> groupedMultHead
-- grouping with Set NodeId
contextsAdded = foldl' (\mapGroups' k ->
let k' = ngramsGroup groupParams k in
case Map.lookup k' mapGroups' of
Nothing -> mapGroups'
Just g -> case Map.lookup k mapTextDocIds of
Nothing -> mapGroups'
Just ns -> Map.insert k' ( g { _gt_nodes = Set.union ns (_gt_nodes g)}) mapGroups'
)
mapGroups
$ Map.keys mapTextDocIds
-- compute cooccurrences -- | Coocurrences computation
mapCooc = Map.filter (>2) --, t1 >= t2 -- permute byAxis diag -- since matrix symmetric
let mapCooc = Map.filter (>2)
$ Map.fromList [ ((t1, t2), Set.size $ Set.intersection s1 s2) $ Map.fromList [ ((t1, t2), Set.size $ Set.intersection s1 s2)
| (t1, s1) <- mapStemNodeIds | (t1, s1) <- mapStemNodeIds
, (t2, s2) <- mapStemNodeIds , (t2, s2) <- mapStemNodeIds
--, t1 >= t2 -- permute byAxis diag -- since matrix symmetric
] ]
where where
mapStemNodeIds = Map.toList $ Map.map (_gt_nodes) contextsAdded mapStemNodeIds = Map.toList
-- printDebug "mapCooc" mapCooc $ Map.map viewScores
$ groupedTreeScores_SetNodeId
let let
-- computing scores -- computing scores
mapScores f = Map.fromList mapScores f = Map.fromList
$ map (\(Scored t g s') -> (t, f (g,s'))) $ map (\g -> (view scored_terms g, f g))
$ normalizeGlobal $ normalizeGlobal
$ map normalizeLocal $ map normalizeLocal
$ scored' mapCooc $ scored' mapCooc
groupsWithScores = catMaybes let
$ map (\(stem, g) groupedTreeScores_SpeGen :: Map Text (GroupedTreeScores (Scored Text))
-> case Map.lookup stem mapScores' of groupedTreeScores_SpeGen = setScoresWithMap (mapScores identity) (groupedMonoHead <> groupedMultHead)
Nothing -> Nothing
Just s' -> Just $ g { _gt_score = s'}
) $ Map.toList contextsAdded
where
mapScores' = mapScores identity
-- adapt2 TOCHECK with DC
-- printDebug "groupsWithScores" groupsWithScores
let let
-- sort / partition / split -- sort / partition / split
-- filter mono/multi again -- filter mono/multi again
(monoScored, multScored) = List.partition (\g -> _gt_size g < 2) groupsWithScores (monoScored, multScored) = Map.partitionWithKey (\t _v -> size t < 2) groupedTreeScores_SpeGen
-- filter with max score -- filter with max score
partitionWithMaxScore = List.partition (\g -> let (s1,s2) = _gt_score g in s1 > s2 ) partitionWithMaxScore = Map.partition (\g -> (view scored_genInc $ view gts'_score g)
> (view scored_speExc $ view gts'_score g)
)
(monoScoredIncl, monoScoredExcl) = partitionWithMaxScore monoScored (monoScoredIncl, monoScoredExcl) = partitionWithMaxScore monoScored
(multScoredIncl, multScoredExcl) = partitionWithMaxScore multScored (multScoredIncl, multScoredExcl) = partitionWithMaxScore multScored
-- splitAt -- splitAt
let let
listSizeLocal = 1000 :: Double -- use % of list if to big, or Int if to small -- use % of list if to big, or Int if to small
listSizeLocal = 1000 :: Double
inclSize = 0.4 :: Double inclSize = 0.4 :: Double
exclSize = 1 - inclSize exclSize = 1 - inclSize
splitAt' n' = List.splitAt (round $ n' * listSizeLocal)
(monoScoredInclHead, monoScoredInclTail) = splitAt' (monoSize * inclSize / 2) $ List.sortOn (Down . _gt_score) monoScoredIncl splitAt' n' = (both (Map.fromList)) . (List.splitAt (round $ n' * listSizeLocal))
(monoScoredExclHead, monoScoredExclTail) = splitAt' (monoSize * inclSize / 2) $ List.sortOn (Down . _gt_score) monoScoredExcl sortOn f = (List.sortOn (Down . (view (gts'_score . f)) . snd)) . Map.toList
monoInc_size = splitAt' $ monoSize * inclSize / 2
(monoScoredInclHead, monoScoredInclTail) = monoInc_size $ (sortOn scored_genInc) monoScoredIncl
(monoScoredExclHead, monoScoredExclTail) = monoInc_size $ (sortOn scored_speExc) monoScoredExcl
(multScoredInclHead, multScoredInclTail) = splitAt' (multSize * exclSize / 2) $ List.sortOn (Down . _gt_score) multScoredIncl multExc_size = splitAt' $ multSize * exclSize / 2
(multScoredExclHead, multScoredExclTail) = splitAt' (multSize * exclSize / 2) $ List.sortOn (Down . _gt_score) multScoredExcl (multScoredInclHead, multScoredInclTail) = multExc_size $ (sortOn scored_genInc) multScoredIncl
(multScoredExclHead, multScoredExclTail) = multExc_size $ (sortOn scored_speExc) multScoredExcl
------------------------------------------------------------
-- Final Step building the Typed list -- Final Step building the Typed list
termListHead = maps <> cands termListHead = maps <> cands
where where
maps = set gt_listType (Just MapTerm) maps = setListType (Just MapTerm)
<$> monoScoredInclHead $ monoScoredInclHead
<> monoScoredExclHead <> monoScoredExclHead
<> multScoredInclHead <> multScoredInclHead
<> multScoredExclHead <> multScoredExclHead
cands = set gt_listType (Just CandidateTerm) cands = setListType (Just CandidateTerm)
<$> monoScoredInclTail $ monoScoredInclTail
<> monoScoredExclTail <> monoScoredExclTail
<> multScoredInclTail <> multScoredInclTail
<> multScoredExclTail <> multScoredExclTail
termListTail = map (set gt_listType (Just CandidateTerm)) ( groupedMonoTail <> groupedMultTail) termListTail = (setListType (Just CandidateTerm)) (groupedMonoTail <> groupedMultTail)
-- printDebug "monoScoredInclHead" monoScoredInclHead
-- printDebug "monoScoredExclHead" monoScoredExclTail
-- printDebug "multScoredInclHead" multScoredInclHead
-- printDebug "multScoredExclTail" multScoredExclTail
let result = Map.unionsWith (<>) let result = Map.unionsWith (<>)
[ Map.fromList [( NgramsTerms, (List.concat $ map toNgramsElement $ termListHead) [ Map.fromList [( nt, toNgramsElement termListHead
<> (List.concat $ map toNgramsElement $ termListTail) <> toNgramsElement termListTail
<> (List.concat $ map toNgramsElement $ stopTerms) <> toNgramsElement stopTerms
)] )]
] ]
-- printDebug "\n result \n" r
pure result
toNgramsElement :: GroupedText a -> [NgramsElement]
toNgramsElement (GroupedText listType label _ setNgrams _ _ _) =
[parentElem] <> childrenElems
where
parent = label
children = Set.toList setNgrams
parentElem = mkNgramsElement (NgramsTerm parent)
(fromMaybe CandidateTerm listType)
Nothing
(mSetFromList (NgramsTerm <$> children))
childrenElems = map (\t -> mkNgramsElement t (fromMaybe CandidateTerm $ listType)
(Just $ RootParent (NgramsTerm parent) (NgramsTerm parent))
(mSetFromList [])
) (NgramsTerm <$> children)
toGargList :: Maybe ListType -> b -> (Maybe ListType, b) pure result
toGargList l n = (l,n)
isStopTerm :: StopSize -> Text -> Bool
isStopTerm (StopSize n) x = Text.length x < n || any isStopChar (Text.unpack x)
where
isStopChar c = not (c `elem` ("- /()%" :: [Char]) || Char.isAlpha c)
------------------------------------------------------------------------------
...@@ -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
where
flow1 = groupWithScores' flc scoring
scoring t = fromMaybe mempty $ Map.lookup t scores
flow2 = case (view flc_cont flow1) == Map.empty of
True -> flow1
False -> groupWithStem' groupParams flow1
------------------------------------------------------------------------
-- | WIP
toGroupedText_test :: Bool -- Map Stem (GroupedText Int)
toGroupedText_test =
-- fromGroupedScores $ fromListScores from
toGroupedText params from datas == result
where
params = GroupedTextParams identity (Set.size . snd) fst snd
from :: Map Text FlowListScores
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)
datas = Map.fromList [("A. Rahmani" , Set.fromList [1,2])
,("T. Reposeur", Set.fromList [3,4])
,("B. Tamain" , Set.fromList [5,6])
]
------------------------------------------------------------------------
setScoresWithMap :: (Ord a, Ord b, Monoid b) => Map Text b
-> Map Text (GroupedTreeScores a)
-> Map Text (GroupedTreeScores b)
setScoresWithMap m = setScoresWith (score m)
where
score m' t = case Map.lookup t m' of
Nothing -> mempty
Just r -> r
result :: Map Stem (GroupedText Int) setScoresWith :: (Ord a, Ord b)
result = Map.fromList [("A. Rahmani",GroupedText {_gt_listType = Nothing => (Text -> b)
,_gt_label = "A. Rahmani" -> Map Text (GroupedTreeScores a)
,_gt_score = 2 -> Map Text (GroupedTreeScores b)
,_gt_children = Set.empty {-
,_gt_size = 2 -- | This Type level lenses solution does not work
,_gt_stem = "A. Rahmani" setScoresWith f = Map.mapWithKey (\k v -> over gts'_children (setScoresWith f)
,_gt_nodes = Set.fromList [1,2] $ set gts'_score (f k) v
}
)
,("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" setScoresWith f = Map.mapWithKey (\k v -> v { _gts'_score = f k
,_gt_score = 2 , _gts'_children = setScoresWith f
,_gt_children = Set.fromList ["A. Rahmani","B. Tamain"] $ view gts'_children v
,_gt_size = 2
,_gt_stem = "T. Reposeur"
,_gt_nodes = Set.fromList [1..6]
} }
) )
]
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | To be removed
addListType :: Map Text ListType -> GroupedText a -> GroupedText a
addListType m g = set gt_listType (hasListType m g) g
where
hasListType :: Map Text ListType -> GroupedText a -> Maybe ListType
hasListType m' (GroupedText _ label _ g' _ _ _) =
List.foldl' (<>) Nothing
$ map (\t -> Map.lookup t m')
$ Set.toList
$ Set.insert label g'
{-|
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
addScore :: Map Text (Set NodeId) orphans = toGroupedTree
-> Map Text (GroupedTextScores (Set NodeId)) $ toMapMaybeParent scores
-> Map Text (GroupedTextScores (Set NodeId)) $ view flc_cont flc
addScore mapNs = Map.mapWithKey scoring ------------------------------------------------------------------------
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 where
maybeParent = keyWithMaxValue $ view fls_parents fs
scoring k g = set gts_score ( Set.unions maybeList = keyWithMaxValue $ view fls_listType fs
$ catMaybes
$ map (\n -> Map.lookup n mapNs) toGroupedTree :: Eq a
$ [k] <> (Set.toList $ view gts_children g) => Map (Maybe Parent) (Map Text (GroupedTreeScores (a)))
) g -> Map Parent (GroupedTreeScores (a))
toGroupedTree m = case Map.lookup Nothing m of
addIfNotExist :: Map Text FlowListScores Nothing -> mempty
-> Map Text (Set NodeId) Just m' -> toGroupedTree' m m'
-> Map Text (GroupedTextScores (Set NodeId))
addIfNotExist mapSocialScores mapScores =
foldl' (addIfNotExist' mapSocialScores) Map.empty $ Map.toList mapScores 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 where
addIfNotExist' mss m (t,ns) = addGroup m' k v = over gts'_children ( (toGroupedTree' m')
case Map.lookup t mss of . (Map.union ( fromMaybe mempty
Nothing -> Map.alter (add ns) t m $ Map.lookup (Just k) m'
_ -> m )
)
)
v
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
...@@ -17,25 +17,25 @@ Portability : POSIX ...@@ -17,25 +17,25 @@ Portability : POSIX
module Gargantext.Core.Text.List.Group.WithStem module Gargantext.Core.Text.List.Group.WithStem
where where
import Control.Lens (makeLenses, view) import Control.Lens (view, over)
import Data.Set (Set) import Data.Set (Set)
import Data.Map (Map) import Data.Map (Map)
import Data.Monoid (mempty)
import Data.Text (Text) import Data.Text (Text)
import Data.Semigroup (Semigroup)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Text (size)
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.Group.WithScores import Gargantext.Core.Text.List.Group.Prelude
import Gargantext.Core.Text.List.Social.Prelude
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.Map as Map import qualified Data.Map as Map
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Text as Text import qualified Data.Text as Text
------------------------------------------------------------------------
-- | Main Types -- | Main Types
data StopSize = StopSize {unStopSize :: !Int} data StopSize = StopSize {unStopSize :: !Int}
deriving (Eq)
-- | TODO: group with 2 terms only can be -- | TODO: group with 2 terms only can be
-- discussed. Main purpose of this is offering -- discussed. Main purpose of this is offering
...@@ -47,81 +47,27 @@ data GroupParams = GroupParams { unGroupParams_lang :: !Lang ...@@ -47,81 +47,27 @@ data GroupParams = GroupParams { unGroupParams_lang :: !Lang
, unGroupParams_stopSize :: !StopSize , unGroupParams_stopSize :: !StopSize
} }
| GroupIdentity | GroupIdentity
deriving (Eq)
------------------------------------------------------------------------
class GroupWithStem a where
groupWithStem' :: GroupParams
-> FlowCont Text (GroupedTreeScores a)
-> FlowCont Text (GroupedTreeScores a)
data GroupedTextParams a b = -- TODO factorize groupWithStem_*
GroupedTextParams { _gt_fun_stem :: Text -> Text instance GroupWithStem (Set NodeId) where
, _gt_fun_score :: a -> b groupWithStem' = groupWithStem_SetNodeId
, _gt_fun_texts :: a -> Set Text
, _gt_fun_nodeIds :: a -> Set NodeId
-- , _gt_fun_size :: a -> Int
}
makeLenses 'GroupedTextParams
type Stem = Text
data GroupedText score =
GroupedText { _gt_listType :: !(Maybe ListType)
, _gt_label :: !Text
, _gt_score :: !score
, _gt_children :: !(Set Text)
, _gt_size :: !Int
, _gt_stem :: !Stem -- needed ?
, _gt_nodes :: !(Set NodeId)
} deriving (Show, Eq) --}
{-
instance Show score => Show (GroupedText score) where
show (GroupedText lt l s _ _ _ _) = show l <> " : " <> show lt <> " : " <> show s
--}
{-
instance (Eq a) => Eq (GroupedText a) where
(==) (GroupedText _ _ score1 _ _ _ _)
(GroupedText _ _ score2 _ _ _ _) = (==) score1 score2
-}
instance (Eq a, Ord a) => Ord (GroupedText a) where
compare (GroupedText _ _ score1 _ _ _ _)
(GroupedText _ _ score2 _ _ _ _) = compare score1 score2
instance Ord a => Semigroup (GroupedText a) where
(<>) (GroupedText lt1 label1 score1 group1 s1 stem1 nodes1)
(GroupedText lt2 label2 score2 group2 s2 stem2 nodes2)
| score1 >= score2 = GroupedText lt label1 score1 (Set.insert label2 gr) s1 stem1 nodes
| otherwise = GroupedText lt label2 score2 (Set.insert label1 gr) s2 stem2 nodes
where
lt = lt1 <> lt2
gr = Set.union group1 group2
nodes = Set.union nodes1 nodes2
-- | Lenses Instances
makeLenses 'GroupedText
------------------------------------------------------------------------ instance GroupWithStem Double where
groupWithStem :: {- ( HasNgrams a groupWithStem' = groupWithStem_Double
, HasGroupWithScores a b
, Semigroup a
, Ord b
)
=> -} GroupedTextParams a b
-> Map Text (GroupedTextScores (Set NodeId))
-> Map Stem (GroupedText Int)
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 groupWith :: GroupParams
-> Text -> Text
-> Text -> Text
ngramsGroup GroupIdentity = identity groupWith GroupIdentity = identity
ngramsGroup (GroupParams l _m _n _) = groupWith (GroupParams l _m _n _) =
Text.intercalate " " Text.intercalate " "
. map (stem l) . map (stem l)
-- . take n -- . take n
...@@ -131,21 +77,149 @@ ngramsGroup (GroupParams l _m _n _) = ...@@ -131,21 +77,149 @@ ngramsGroup (GroupParams l _m _n _) =
. Text.replace "-" " " . Text.replace "-" " "
------------------------------------------------------------------------ ------------------------------------------------------------------------
groupedTextWithStem :: Ord b groupWithStem_SetNodeId :: GroupParams
=> GroupedTextParams a b -> FlowCont Text (GroupedTreeScores (Set NodeId))
-> Map Text a -> FlowCont Text (GroupedTreeScores (Set NodeId))
-> Map Stem (GroupedText b) groupWithStem_SetNodeId g flc
groupedTextWithStem gparams from = | g == GroupIdentity = FlowCont ( (<>)
Map.fromListWith (<>) $ map (group gparams) $ Map.toList from (view flc_scores flc)
(view flc_cont flc)
) mempty
| otherwise = mergeWith (groupWith g) flc
groupWithStem_Double :: GroupParams
-> FlowCont Text (GroupedTreeScores Double)
-> FlowCont Text (GroupedTreeScores Double)
groupWithStem_Double g flc
| g == GroupIdentity = FlowCont ( (<>)
(view flc_scores flc)
(view flc_cont flc)
) mempty
| otherwise = mergeWith_Double (groupWith g) flc
-- | MergeWith : with stem, we always have an answer
-- if Maybe lems then we should add it to continuation
mergeWith :: (Text -> Text)
-> FlowCont Text (GroupedTreeScores (Set NodeId))
-> FlowCont Text (GroupedTreeScores (Set NodeId))
mergeWith fun flc = FlowCont scores mempty
where where
group gparams' (t,d) = let t' = (view gt_fun_stem gparams') t
in (t', GroupedText scores :: Map Text (GroupedTreeScores (Set NodeId))
Nothing scores = foldl' (alter (mapStems scores')) scores' cont'
t where
((view gt_fun_score gparams') d) scores' = view flc_scores flc
((view gt_fun_texts gparams') d) cont' = Map.toList $ view flc_cont flc
(size t)
t' -- TODO insert at the right place in group hierarchy
((view gt_fun_nodeIds gparams') d) -- adding as child of the parent for now
) alter :: Map Stem Text
------------------------------------------------------------------------ -> Map Text (GroupedTreeScores (Set NodeId))
-> (Text, GroupedTreeScores (Set NodeId))
-> Map Text (GroupedTreeScores (Set NodeId))
alter st target (t,g) = case Map.lookup t st of
Nothing -> Map.alter (alter' (t,g)) t target
Just t' -> Map.alter (alter' (t,g)) t' target
alter' (_t,g) Nothing = Just g
alter' ( t,g) (Just g') = Just $ over gts'_children
( Map.union (Map.singleton t g))
g'
mapStems :: Map Text (GroupedTreeScores (Set NodeId))
-> Map Stem Text
mapStems = (Map.fromListWith (<>)) . List.concat . (map mapStem) . Map.toList
mapStem :: (Text, GroupedTreeScores (Set NodeId))
-> [(Stem, Text)]
mapStem (s,g) = parent : children
where
parent = (fun s, s)
children = List.concat $ map mapStem (Map.toList $ view gts'_children g)
-- | MergeWith : with stem, we always have an answer
-- if Maybe lems then we should add it to continuation
mergeWith_Double :: (Text -> Text)
-> FlowCont Text (GroupedTreeScores Double)
-> FlowCont Text (GroupedTreeScores Double)
mergeWith_Double fun flc = FlowCont scores mempty
where
scores :: Map Text (GroupedTreeScores Double)
scores = foldl' (alter (mapStems scores')) scores' cont'
where
scores' = view flc_scores flc
cont' = Map.toList $ view flc_cont flc
-- TODO insert at the right place in group hierarchy
-- adding as child of the parent for now
alter :: Map Stem Text
-> Map Text (GroupedTreeScores Double)
-> (Text, GroupedTreeScores Double)
-> Map Text (GroupedTreeScores Double)
alter st target (t,g) = case Map.lookup t st of
Nothing -> Map.alter (alter' (t,g)) t target
Just t' -> Map.alter (alter' (t,g)) t' target
alter' (_t,g) Nothing = Just g
alter' ( t,g) (Just g') = Just $ over gts'_children
( Map.union (Map.singleton t g))
g'
mapStems :: Map Text (GroupedTreeScores Double)
-> Map Stem Text
mapStems = (Map.fromListWith (<>)) . List.concat . (map mapStem) . Map.toList
mapStem :: (Text, GroupedTreeScores Double)
-> [(Stem, Text)]
mapStem (s,g) = parent : children
where
parent = (fun s, s)
children = List.concat $ map mapStem (Map.toList $ view gts'_children g)
{-
-- | TODO fixme
mergeWith_a :: (Text -> Text)
-> FlowCont Text (GroupedTreeScores a)
-> FlowCont Text (GroupedTreeScores a)
mergeWith_a fun flc = FlowCont scores mempty
where
scores :: Map Text (GroupedTreeScores a)
scores = foldl' (alter (mapStems scores')) scores' cont'
where
scores' = view flc_scores flc
cont' = Map.toList $ _flc_cont flc
-- TODO insert at the right place in group hierarchy
-- adding as child of the parent for now
alter :: Map Stem Text
-> Map Text (GroupedTreeScores a)
-> (Text, GroupedTreeScores a)
-> Map Text (GroupedTreeScores a)
alter st target (t,g) = case Map.lookup t st of
Nothing -> Map.alter (alter' (t,g)) t target
Just t' -> Map.alter (alter' (t,g)) t' target
alter' (_t,g) Nothing = Just g
alter' ( t,g) (Just g') = Just $ over gts'_children
( Map.union (Map.singleton t g))
g'
mapStems :: Map Text (GroupedTreeScores a)
-> Map Stem Text
mapStems = (Map.fromListWith (<>)) . List.concat . (map mapStem) . Map.toList
mapStem :: (Text, GroupedTreeScores a)
-> [(Stem, Text)]
mapStem (s,g) = parent : children
where
parent = (fun s, s)
children = List.concat $ map mapStem (Map.toList $ view gts'_children g)
-}
...@@ -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,6 +39,12 @@ flowSocialListPriority :: FlowSocialListPriority -> [NodeMode] ...@@ -74,6 +39,12 @@ flowSocialListPriority :: FlowSocialListPriority -> [NodeMode]
flowSocialListPriority MySelfFirst = [Private, Shared{-, Public -}] flowSocialListPriority MySelfFirst = [Private, Shared{-, Public -}]
flowSocialListPriority OthersFirst = reverse $ flowSocialListPriority MySelfFirst flowSocialListPriority OthersFirst = reverse $ flowSocialListPriority MySelfFirst
-- | We keep the parents for all ngrams but terms
keepAllParents :: NgramsType -> KeepAllParents
keepAllParents NgramsTerms = KeepAllParents False
keepAllParents _ = KeepAllParents True
------------------------------------------------------------------------ ------------------------------------------------------------------------
flowSocialList' :: ( RepoCmdM env err m flowSocialList' :: ( RepoCmdM env err m
, CmdM env err m , CmdM env err m
...@@ -81,119 +52,38 @@ flowSocialList' :: ( RepoCmdM env err m ...@@ -81,119 +52,38 @@ flowSocialList' :: ( RepoCmdM env err m
, HasTreeError err , HasTreeError err
) )
=> FlowSocialListPriority => FlowSocialListPriority
-> User -> NgramsType -> Set Text -> User -> NgramsType
-> m (Map Text FlowListScores) -> FlowCont Text FlowListScores
flowSocialList' flowPriority user nt ngrams' = -> m (FlowCont Text FlowListScores)
parentUnionsExcl <$> mapM (flowSocialListByMode' user nt ngrams') flowSocialList' flowPriority user nt flc =
mconcat <$> mapM (flowSocialListByMode' user nt flc)
(flowSocialListPriority flowPriority) (flowSocialListPriority flowPriority)
where
------------------------------------------------------------------------ flowSocialListByMode' :: ( RepoCmdM env err m
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 , CmdM env err m
, HasNodeError err , HasNodeError err
, HasTreeError err , HasTreeError err
) )
=> User -> NgramsType -> Set Text -> NodeMode => User -> NgramsType
-> m (Map Text FlowListScores) -> FlowCont Text FlowListScores
flowSocialListByMode' user nt st mode = -> NodeMode
findListsId user mode -> m (FlowCont Text FlowListScores)
>>= flowSocialListByModeWith nt st flowSocialListByMode' user' nt' flc' mode =
findListsId user' mode
>>= flowSocialListByModeWith nt' flc'
flowSocialListByModeWith :: ( RepoCmdM env err m flowSocialListByModeWith :: ( RepoCmdM env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
, HasTreeError err , HasTreeError err
) )
=> NgramsType -> Set Text -> [NodeId] => NgramsType
-> m (Map Text FlowListScores) -> FlowCont Text FlowListScores
flowSocialListByModeWith nt st ns = -> [NodeId]
mapM (\l -> getListNgrams [l] nt) ns -> m (FlowCont Text FlowListScores)
flowSocialListByModeWith nt'' flc'' ns =
mapM (\l -> getListNgrams [l] nt'') ns
>>= pure >>= pure
. toFlowListScores (keepAllParents nt) st Map.empty . toFlowListScores (keepAllParents nt'') flc''
-- | We keep the parents for all ngrams but terms
keepAllParents :: NgramsType -> KeepAllParents
keepAllParents NgramsTerms = KeepAllParents False
keepAllParents _ = KeepAllParents True
------------------------------------------------------------------------
-- TODO: maybe use social groups too
-- | TODO what if equality ?
-- choice depends on Ord instance of ListType
-- for now : data ListType = StopTerm | CandidateTerm | MapTerm
-- means MapTerm > CandidateTerm > StopTerm in case of equality of counts
-- (we minimize errors on MapTerms if doubt)
toSocialList :: Map Text (Map ListType Int)
-> Set Text
-> Map (Maybe ListType) (Set Text)
toSocialList m = Map.fromListWith (<>)
. Set.toList
. Set.map (toSocialList1 m)
toSocialList1 :: Map Text (Map ListType Int)
-> Text
-> (Maybe ListType, Set Text)
toSocialList1 m t = case Map.lookup t m of
Nothing -> (Nothing, Set.singleton t)
Just m' -> ( (fst . fst) <$> Map.maxViewWithKey m'
, 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)
]
------------------------------------------------------------------------
-- | Tools
------------------------------------------------------------------------
termsByList :: ListType -> (Map (Maybe ListType) (Set Text)) -> Set Text
termsByList CandidateTerm m = Set.unions
$ map (\lt -> fromMaybe Set.empty $ Map.lookup lt m)
[ Nothing, Just CandidateTerm ]
termsByList l m =
fromMaybe Set.empty $ Map.lookup (Just l) m
------------------------------------------------------------------------
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
(Set.fromList $ Map.keys $ view flc_cont flc_origin')
toFlowListScores'' :: KeepAllParents toFlowListScores_Level2 :: KeepAllParents
-> Set Text
-> Map Text NgramsRepoElement -> Map Text NgramsRepoElement
-> Map Text FlowListScores -> FlowCont Text FlowListScores
-> FlowCont Text FlowListScores
-> Text -> Text
-> Map Text FlowListScores -> FlowCont Text FlowListScores
toFlowListScores'' k'' ss ngramsRepo to'' t = 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
...@@ -52,7 +52,7 @@ data NewUser a = NewUser { _nu_username :: Username ...@@ -52,7 +52,7 @@ data NewUser a = NewUser { _nu_username :: Username
deriving (Show) deriving (Show)
arbitraryUsername :: [Username] arbitraryUsername :: [Username]
arbitraryUsername = ["gargantua"] <> users arbitraryUsername = {- ["gargantua"] <> -} users
where where
users = zipWith (\a b -> a <> (pack . show) b) users = zipWith (\a b -> a <> (pack . show) b)
(repeat "user") ([1..20]::[Int]) (repeat "user") ([1..20]::[Int])
...@@ -68,12 +68,13 @@ toUserHash (NewUser u m (GargPassword p)) = do ...@@ -68,12 +68,13 @@ toUserHash (NewUser u m (GargPassword p)) = do
h <- Auth.createPasswordHash p h <- Auth.createPasswordHash p
pure $ NewUser u m h pure $ NewUser u m h
-- TODO remove
arbitraryUsersHash :: MonadIO m arbitraryUsersHash :: MonadIO m
=> m [NewUser HashPassword] => m [NewUser HashPassword]
arbitraryUsersHash = mapM toUserHash arbitraryUsers arbitraryUsersHash = mapM toUserHash arbitraryNewUsers
arbitraryUsers :: [NewUser GargPassword] arbitraryNewUsers :: [NewUser GargPassword]
arbitraryUsers = map (\u -> NewUser u (u <> "@gargantext.org") (GargPassword $ reverse u)) arbitraryNewUsers = map (\u -> NewUser u (u <> "@gargantext.org") (GargPassword $ reverse u))
arbitraryUsername arbitraryUsername
...@@ -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
......
...@@ -32,13 +32,12 @@ publicNodeTypes :: [NodeType] ...@@ -32,13 +32,12 @@ publicNodeTypes :: [NodeType]
publicNodeTypes = [NodeDashboard, NodeGraph, NodePhylo, NodeFile] publicNodeTypes = [NodeDashboard, NodeGraph, NodePhylo, NodeFile]
------------------------------------------------------------------------ ------------------------------------------------------------------------
data ShareNodeWith = ShareNodeWith_User { snwu_nodetype :: NodeType data ShareNodeWith = ShareNodeWith_User { snwu_nodetype :: NodeType
, snwu_user :: User } , snwu_user :: User
}
| ShareNodeWith_Node { snwn_nodetype :: NodeType | ShareNodeWith_Node { snwn_nodetype :: NodeType
, snwn_node_id :: NodeId , snwn_node_id :: NodeId
} }
------------------------------------------------------------------------ ------------------------------------------------------------------------
shareNodeWith :: HasNodeError err shareNodeWith :: HasNodeError err
=> ShareNodeWith => ShareNodeWith
...@@ -86,7 +85,6 @@ delFolderTeam u nId = do ...@@ -86,7 +85,6 @@ delFolderTeam u nId = do
folderSharedId <- getFolderId u NodeFolderShared folderSharedId <- getFolderId u NodeFolderShared
deleteNodeNode folderSharedId nId deleteNodeNode folderSharedId nId
unPublish :: HasNodeError err unPublish :: HasNodeError err
=> ParentId -> NodeId => ParentId -> NodeId
-> Cmd err Int -> Cmd err Int
......
...@@ -27,16 +27,25 @@ import Gargantext.Prelude ...@@ -27,16 +27,25 @@ import Gargantext.Prelude
getUserId :: HasNodeError err getUserId :: HasNodeError err
=> User => User
-> Cmd err UserId -> Cmd err UserId
getUserId (UserDBId uid) = pure uid getUserId u = do
getUserId (RootId rid) = do maybeUser <- getUserId' u
case maybeUser of
Nothing -> nodeError NoUserFound
Just u' -> pure u'
getUserId' :: HasNodeError err
=> User
-> Cmd err (Maybe UserId)
getUserId' (UserDBId uid) = pure (Just uid)
getUserId' (RootId rid) = do
n <- getNode rid n <- getNode rid
pure $ _node_userId n pure $ Just $ _node_userId n
getUserId (UserName u ) = do getUserId' (UserName u ) = do
muser <- getUser u muser <- getUser u
case muser of case muser of
Just user -> pure $ userLight_id user Just user -> pure $ Just $ userLight_id user
Nothing -> nodeError NoUserFound Nothing -> pure Nothing
getUserId UserPublic = nodeError NoUserFound getUserId' UserPublic = pure Nothing
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Username = Text -- | Username = Text
......
...@@ -26,7 +26,7 @@ import Gargantext.Prelude ...@@ -26,7 +26,7 @@ import Gargantext.Prelude
import Gargantext.Prelude.Config import Gargantext.Prelude.Config
import Gargantext.Prelude.Crypto.Pass.User (gargPass) import Gargantext.Prelude.Crypto.Pass.User (gargPass)
import Gargantext.Prelude.Mail (gargMail, GargMail(..)) import Gargantext.Prelude.Mail (gargMail, GargMail(..))
import qualified Data.List as List
------------------------------------------------------------------------ ------------------------------------------------------------------------
type EmailAddress = Text type EmailAddress = Text
...@@ -42,14 +42,20 @@ newUserQuick :: (MonadRandom m) ...@@ -42,14 +42,20 @@ newUserQuick :: (MonadRandom m)
=> Text -> m (NewUser GargPassword) => Text -> m (NewUser GargPassword)
newUserQuick n = do newUserQuick n = do
pass <- gargPass pass <- gargPass
let (u,_m) = guessUserName n let u = case guessUserName n of
Just (u', _m) -> u'
Nothing -> panic "[G.D.A.U.N.newUserQuick]: Email invalid"
pure (NewUser u n (GargPassword pass)) pure (NewUser u n (GargPassword pass))
guessUserName :: Text -> (Text,Text) ------------------------------------------------------------------------
isEmail :: Text -> Bool
isEmail = ((==) 2) . List.length . (splitOn "@")
guessUserName :: Text -> Maybe (Text,Text)
guessUserName n = case splitOn "@" n of guessUserName n = case splitOn "@" n of
[u',m'] -> if m' /= "" then (u',m') [u',m'] -> if m' /= "" then Just (u',m')
else panic "Email Invalid" else Nothing
_ -> panic "Email invalid" _ -> Nothing
------------------------------------------------------------------------ ------------------------------------------------------------------------
newUser' :: HasNodeError err newUser' :: HasNodeError err
=> Text -> NewUser GargPassword -> Cmd err Int64 => Text -> NewUser GargPassword -> Cmd err Int64
...@@ -64,12 +70,17 @@ newUsers' address us = do ...@@ -64,12 +70,17 @@ newUsers' address us = do
_ <- liftBase $ mapM (mail Invitation address) us _ <- liftBase $ mapM (mail Invitation address) us
pure r pure r
------------------------------------------------------------------------ ------------------------------------------------------------------------
data SendEmail = SendEmail Bool
updateUser :: HasNodeError err updateUser :: HasNodeError err
=> Text -> NewUser GargPassword -> Cmd err Int64 => SendEmail -> Text -> NewUser GargPassword -> Cmd err Int64
updateUser address u = do updateUser (SendEmail send) address u = do
u' <- liftBase $ toUserHash u u' <- liftBase $ toUserHash u
n <- updateUserDB $ toUserWrite u' n <- updateUserDB $ toUserWrite u'
_ <- liftBase $ mail Update address u _ <- case send of
True -> liftBase $ mail Update address u
False -> pure ()
pure n pure n
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -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
......
...@@ -80,10 +80,17 @@ type CmdM env err m = ...@@ -80,10 +80,17 @@ type CmdM env err m =
, HasConfig env , HasConfig env
) )
type CmdRandom env err m =
( CmdM' env err m
, HasConnectionPool env
, HasConfig env
, MonadRandom m
)
type Cmd'' env err a = forall m. CmdM'' env err m => m a type Cmd'' env err a = forall m. CmdM'' env err m => m a
type Cmd' env err a = forall m. CmdM' env err m => m a type Cmd' env err a = forall m. CmdM' env err m => m a
type Cmd err a = forall m env. CmdM env err m => m a type Cmd err a = forall m env. CmdM env err m => m a
type CmdR err a = forall m env. CmdRandom env err m => m a
......
...@@ -24,7 +24,7 @@ module Gargantext.Database.Query.Table.User ...@@ -24,7 +24,7 @@ module Gargantext.Database.Query.Table.User
, updateUserDB , updateUserDB
, queryUserTable , queryUserTable
, getUser , getUser
, insertUsersDemo , insertNewUsers
, selectUsersLightWith , selectUsersLightWith
, userWithUsername , userWithUsername
, userWithId , userWithId
...@@ -141,9 +141,9 @@ getUser u = userLightWithUsername u <$> usersLight ...@@ -141,9 +141,9 @@ getUser u = userLightWithUsername u <$> usersLight
---------------------------------------------------------------------- ----------------------------------------------------------------------
insertUsersDemo :: Cmd err Int64 insertNewUsers :: [NewUser GargPassword] -> Cmd err Int64
insertUsersDemo = do insertNewUsers newUsers = do
users <- liftBase arbitraryUsersHash users <- liftBase $ mapM toUserHash newUsers
insertUsers $ map toUserWrite users insertUsers $ map toUserWrite users
---------------------------------------------------------------------- ----------------------------------------------------------------------
......
...@@ -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