2 Module : Gargantext.Database.Learn
3 Description : Learn Small Data Analytics with big data connection (DB)
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE NoImplicitPrelude #-}
13 {-# LANGUAGE QuasiQuotes #-}
14 {-# LANGUAGE RankNTypes #-}
15 {-# LANGUAGE OverloadedStrings #-}
16 {-# LANGUAGE FlexibleContexts #-}
17 {-# LANGUAGE MonoLocalBinds #-}
19 module Gargantext.Database.Learn where
21 import Data.Text (Text)
22 import Data.Tuple (snd)
24 import Gargantext.Database.Facet
25 import Gargantext.Database.Types.Node
26 import Gargantext.Prelude
27 import Gargantext.Text.Learn
28 import qualified Data.List as List
29 import qualified Data.Text as Text
30 import Gargantext.Database.Schema.NodeNode (nodeNodesCategory)
31 --import Gargantext.Database.Utils (Cmd)
32 --import Gargantext.Database.Schema.Node (HasNodeError)
34 import Gargantext.API.Settings
35 import Gargantext.Database.Flow (FlowCmdM)
37 data FavOrTrash = IsFav | IsTrash
41 --moreLike :: FlowCmdM env error m => FavOrTrash -> CorpusId -> m (Events Bool, [FacetDoc])
43 moreLike :: FlowCmdM DevEnv GargError m => FavOrTrash -> CorpusId -> m [FacetDoc]
45 priors <- getPriors ft cId
46 moreLikeWith priors ft cId
49 ---------------------------------------------------------------------------
50 getPriors :: FlowCmdM DevEnv GargError m => FavOrTrash -> CorpusId -> m (Events Bool)
52 docs_trash <- runViewDocuments cId True Nothing Nothing Nothing
54 docs_fav <- filter (\(FacetDoc _ _ _ _ f _) -> f == 2)
55 <$> runViewDocuments cId False Nothing Nothing Nothing
58 let priors = priorEventsWith text (fav2bool ft) ( List.zip (repeat False) docs_fav
59 <> List.zip (repeat True ) docs_trash
64 moreLikeWith :: FlowCmdM DevEnv GargError m => Events Bool -> FavOrTrash -> CorpusId -> m [FacetDoc]
65 moreLikeWith priors ft cId = do
67 docs_test <- filter (\(FacetDoc _ _ _ _ f _) -> f == 0)
68 <$> runViewDocuments cId False Nothing Nothing Nothing
71 $ filter ((==) (Just $ not $ fav2bool ft) . snd)
72 $ map (\f -> (f, detectDefaultWithPriors text priors f)) docs_test
76 ---------------------------------------------------------------------------
77 fav2bool :: FavOrTrash -> Bool
78 fav2bool ft = if (==) ft IsFav then True else False
81 text :: FacetDoc -> Text
82 text (FacetDoc _ _ _ h _ _) = title <> "" <> Text.take 100 abstr
84 title = maybe "" identity (_hyperdataDocument_title h)
85 abstr = maybe "" identity (_hyperdataDocument_abstract h)
87 ---------------------------------------------------------------------------
89 apply :: (FlowCmdM DevEnv GargError m) => FavOrTrash -> CorpusId -> [NodeId] -> m [Int]
90 apply favTrash cId ns = case favTrash of
91 IsFav -> nodeNodesCategory $ map (\n -> (cId, n, 2)) ns
92 IsTrash -> nodeNodesCategory $ map (\n -> (cId, n, 0)) ns
94 moreLikeAndApply :: FlowCmdM DevEnv GargError m => FavOrTrash -> CorpusId -> m [Int]
95 moreLikeAndApply ft cId = do
96 priors <- getPriors ft cId
97 moreLikeWithAndApply priors ft cId
99 moreLikeWithAndApply :: FlowCmdM DevEnv GargError m => Events Bool -> FavOrTrash -> CorpusId -> m [Int]
100 moreLikeWithAndApply priors ft cId = do
101 ids <- map facetDoc_id <$> moreLikeWith priors ft cId