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

[FIX] warnings

parent 0ed6cf38
...@@ -73,7 +73,7 @@ library: ...@@ -73,7 +73,7 @@ library:
- Gargantext.Core.Text.Corpus.API - Gargantext.Core.Text.Corpus.API
- Gargantext.Core.Text.Corpus.Parsers.CSV - Gargantext.Core.Text.Corpus.Parsers.CSV
- Gargantext.Core.Text.Examples - Gargantext.Core.Text.Examples
- Gargantext.Core.Text.List.CSV - Gargantext.Core.Text.List.Formats.CSV
- Gargantext.Core.Text.Metrics - Gargantext.Core.Text.Metrics
- Gargantext.Core.Text.Metrics.TFICF - Gargantext.Core.Text.Metrics.TFICF
- Gargantext.Core.Text.Metrics.CharByChar - Gargantext.Core.Text.Metrics.CharByChar
......
...@@ -9,6 +9,7 @@ Portability : POSIX ...@@ -9,6 +9,7 @@ Portability : POSIX
-} -}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.Core.Text.List module Gargantext.Core.Text.List
...@@ -30,7 +31,6 @@ import qualified Data.Text as Text ...@@ -30,7 +31,6 @@ import qualified Data.Text as Text
-- import Gargantext.API.Ngrams.Tools (getCoocByNgrams', Diagonal(..)) -- import Gargantext.API.Ngrams.Tools (getCoocByNgrams', Diagonal(..))
import Gargantext.API.Ngrams.Types (NgramsElement, mkNgramsElement, NgramsTerm(..), RootParent(..), mSetFromList) 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 (size)
import Gargantext.Core.Text.List.Social (flowSocialList, flowSocialList', FlowSocialListPriority(..), invertForw) import Gargantext.Core.Text.List.Social (flowSocialList, flowSocialList', FlowSocialListPriority(..), invertForw)
import Gargantext.Core.Text.List.Social.Scores (FlowListScores) import Gargantext.Core.Text.List.Social.Scores (FlowListScores)
import Gargantext.Core.Text.List.Group import Gargantext.Core.Text.List.Group
...@@ -39,7 +39,7 @@ import Gargantext.Core.Text.Metrics (scored', Scored(..), normalizeGlobal, norma ...@@ -39,7 +39,7 @@ import Gargantext.Core.Text.Metrics (scored', Scored(..), normalizeGlobal, norma
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.Admin.Types.Node (NodeId)
import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsUser, groupNodesByNgramsWith, 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.Prelude (CmdM) import Gargantext.Database.Prelude (CmdM)
import Gargantext.Database.Query.Table.Node (defaultList) import Gargantext.Database.Query.Table.Node (defaultList)
...@@ -92,26 +92,10 @@ buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do ...@@ -92,26 +92,10 @@ buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do
let let
groupParams = GroupedTextParams groupIt (Set.size . snd) fst snd {-(size . fst)-} groupParams = GroupedTextParams groupIt (Set.size . snd) fst snd {-(size . fst)-}
grouped' = toGroupedText groupParams socialLists' ngs' groupedWithList = toGroupedText groupParams socialLists' ngs'
-- 8< 8< 8< 8< 8< 8< 8<
let
ngs :: Map Text (Set Text, Set NodeId) = groupNodesByNgramsWith groupIt ngs'
socialLists <- flowSocialList user nt (Set.fromList $ Map.keys ngs)
-- >8 >8 >8 >8 >8 >8 >8
let
grouped = groupedTextWithStem (GroupedTextParams groupIt (Set.size . snd) fst snd {-(size . fst)-} ) -- socialLists'
$ Map.mapWithKey (\k (a,b) -> (Set.delete k a, b))
$ ngs
(stopTerms, tailTerms) = Map.partition (\t -> t ^. gt_listType == Just StopTerm) groupedWithList
let (mapTerms, tailTerms') = Map.partition (\t -> t ^. gt_listType == Just MapTerm) tailTerms
groupedWithList = map (addListType (invertForw socialLists)) grouped
(stopTerms, tailTerms) = Map.partition (\t -> t ^. gt_listType == Just StopTerm)
groupedWithList
(mapTerms, tailTerms') = Map.partition (\t -> t ^. gt_listType == Just MapTerm)
tailTerms
listSize = mapListSize - (List.length mapTerms) listSize = mapListSize - (List.length mapTerms)
(mapTerms', candiTerms) = List.splitAt listSize (mapTerms', candiTerms) = List.splitAt listSize
...@@ -126,6 +110,7 @@ buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do ...@@ -126,6 +110,7 @@ buildNgramsOthersList user uCid groupIt (nt, MapListSize mapListSize) = do
$ map (set gt_listType (Just CandidateTerm)) candiTerms) $ map (set gt_listType (Just CandidateTerm)) candiTerms)
)] )]
-- TODO use ListIds -- TODO use ListIds
buildNgramsTermsList :: ( HasNodeError err buildNgramsTermsList :: ( HasNodeError err
, CmdM env err m , CmdM env err m
......
...@@ -18,27 +18,19 @@ Portability : POSIX ...@@ -18,27 +18,19 @@ Portability : POSIX
module Gargantext.Core.Text.List.Group module Gargantext.Core.Text.List.Group
where where
import Data.Maybe (fromMaybe) import Control.Lens (set)
import Control.Lens (makeLenses, set, (^.))
import Data.Set (Set) import Data.Set (Set)
import Data.Map (Map) import Data.Map (Map)
import Data.Text (Text) import Data.Text (Text)
import Data.Semigroup (Semigroup, (<>))
import Gargantext.Core (Lang(..))
import Gargantext.Core.Text (size)
import Gargantext.Core.Types (ListType(..)) -- (MasterCorpusId, UserCorpusId) import Gargantext.Core.Types (ListType(..)) -- (MasterCorpusId, UserCorpusId)
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Database.Admin.Types.Node (NodeId)
-- import Gargantext.Core.Text.List.Learn (Model(..)) import Gargantext.Core.Text.List.Social.Scores (FlowListScores(..))
import Gargantext.Core.Text.List.Social.Scores (FlowListScores(..), flc_lists, flc_parents, keyWithMaxValue)
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.Core.Text.Terms.Mono.Stem (stem)
import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Set as Set 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
------------------------------------------------------------------------ ------------------------------------------------------------------------
toGroupedText :: GroupedTextParams a b toGroupedText :: GroupedTextParams a b
......
...@@ -14,25 +14,17 @@ Portability : POSIX ...@@ -14,25 +14,17 @@ Portability : POSIX
module Gargantext.Core.Text.List.Group.WithScores module Gargantext.Core.Text.List.Group.WithScores
where where
import Data.Maybe (fromMaybe) import Control.Lens (makeLenses, set, over, view)
import Control.Lens (makeLenses, set, (^.), (%~), over, view)
import Data.Set (Set) import Data.Set (Set)
import Data.Map (Map) import Data.Map (Map)
import Data.Text (Text) import Data.Text (Text)
import Data.Semigroup (Semigroup, (<>))
import Gargantext.Core (Lang(..))
import Gargantext.Core.Text (size)
import Gargantext.Core.Types (ListType(..)) -- (MasterCorpusId, UserCorpusId) import Gargantext.Core.Types (ListType(..)) -- (MasterCorpusId, UserCorpusId)
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Database.Admin.Types.Node (NodeId)
-- import Gargantext.Core.Text.List.Learn (Model(..)) -- import Gargantext.Core.Text.List.Learn (Model(..))
import Gargantext.Core.Text.List.Social.Scores import Gargantext.Core.Text.List.Social.Scores
import Gargantext.Core.Text.Terms.Mono.Stem (stem)
import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Set as Set 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.Text as Text
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -66,7 +58,7 @@ groupWithScores scores = ...@@ -66,7 +58,7 @@ groupWithScores scores =
scoresToGroupedTextScores :: Maybe GroupedWithListScores scoresToGroupedTextScores :: Maybe GroupedWithListScores
-> Text -> Set NodeId -> Text -> Set NodeId
-> GroupedTextScores (Set NodeId) -> GroupedTextScores (Set NodeId)
scoresToGroupedTextScores Nothing t ns = GroupedTextScores Nothing ns Set.empty scoresToGroupedTextScores Nothing _ ns = GroupedTextScores Nothing ns Set.empty
scoresToGroupedTextScores (Just g) t ns = GroupedTextScores list ns (Set.singleton t) scoresToGroupedTextScores (Just g) t ns = GroupedTextScores list ns (Set.singleton t)
where where
list = view gwls_listType g list = view gwls_listType g
...@@ -78,7 +70,7 @@ toGroupedWithListScores ms = foldl' (toGroup ms) Map.empty (Map.toList ms) ...@@ -78,7 +70,7 @@ toGroupedWithListScores ms = foldl' (toGroup ms) Map.empty (Map.toList ms)
-> Map Text GroupedWithListScores -> Map Text GroupedWithListScores
-> (Text, FlowListScores) -> (Text, FlowListScores)
-> Map Text GroupedWithListScores -> Map Text GroupedWithListScores
toGroup ms' result (t,fs) = case (keyWithMaxValue $ view flc_parents fs) of toGroup _ result (t,fs) = case (keyWithMaxValue $ view flc_parents fs) of
Nothing -> Map.alter (addGroupedParent (t,fs)) t result Nothing -> Map.alter (addGroupedParent (t,fs)) t result
Just parent -> Map.alter (addGroupedChild (t,fs)) parent result Just parent -> Map.alter (addGroupedChild (t,fs)) parent result
......
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