]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Text/Terms.hs
[WORKFLOW] Unsupervised ngrams extraction implemented.
[gargantext.git] / src / Gargantext / Text / Terms.hs
1 {-|
2 Module : Gargantext.Text.Ngrams
3 Description : Ngrams definition and tools
4 Copyright : (c) CNRS, 2017 - present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 An @n-gram@ is a contiguous sequence of n items from a given sample of
11 text. In Gargantext application the items are words, n is a non negative
12 integer.
13
14 Using Latin numerical prefixes, an n-gram of size 1 is referred to as a
15 "unigram"; size 2 is a "bigram" (or, less commonly, a "digram"); size
16 3 is a "trigram". English cardinal numbers are sometimes used, e.g.,
17 "four-gram", "five-gram", and so on.
18
19 Source: https://en.wikipedia.org/wiki/Ngrams
20
21 TODO
22 group Ngrams -> Tree
23 compute occ by node of Tree
24 group occs according groups
25
26 compute cooccurrences
27 compute graph
28
29 -}
30
31 {-# LANGUAGE NoImplicitPrelude #-}
32 {-# LANGUAGE TemplateHaskell #-}
33
34 module Gargantext.Text.Terms
35 where
36
37 import Control.Lens
38 import Data.Text (Text)
39 import Data.Traversable
40 import GHC.Base (String)
41
42 import Gargantext.Prelude
43 import Gargantext.Core
44 import Gargantext.Core.Types
45 import Gargantext.Text.Terms.Multi (multiterms)
46 import Gargantext.Text.Terms.Mono (monoTerms)
47 import Gargantext.Text.Terms.Mono.Stem (stem)
48
49 import qualified Data.Set as Set
50 import qualified Data.List as List
51 import qualified Data.Text as Text
52 import Gargantext.Text (sentences)
53 import Gargantext.Text.Terms.Mono.Token.En (tokenize)
54 import Gargantext.Text.Terms.Eleve (mainEleveWith, Tries, Token, buildTries, toToken)
55
56 data TermType lang
57 = Mono { _tt_lang :: lang }
58 | Multi { _tt_lang :: lang }
59 | MonoMulti { _tt_lang :: lang }
60 | Unsupervised { _tt_lang :: lang
61 , _tt_size :: Int
62 , _tt_model :: Maybe (Tries Token ())
63 }
64 makeLenses ''TermType
65
66 --group :: [Text] -> [Text]
67 --group = undefined
68
69 -- remove Stop Words
70 -- map (filter (\t -> not . elem t)) $
71 ------------------------------------------------------------------------
72 -- | Sugar to extract terms from text (hiddeng mapM from end user).
73 --extractTerms :: Traversable t => TermType Lang -> t Text -> IO (t [Terms])
74 extractTerms :: TermType Lang -> [Text] -> IO [[Terms]]
75
76 extractTerms (Unsupervised l n m) xs = mapM (terms (Unsupervised l n (Just m'))) xs
77 where
78 m' = case m of
79 Just m''-> m''
80 Nothing -> newTries n (Text.intercalate " " xs)
81
82 extractTerms termTypeLang xs = mapM (terms termTypeLang) xs
83
84
85
86 ------------------------------------------------------------------------
87 -- | Terms from Text
88 -- Mono : mono terms
89 -- Multi : multi terms
90 -- MonoMulti : mono and multi
91 -- TODO : multi terms should exclude mono (intersection is not empty yet)
92 terms :: TermType Lang -> Text -> IO [Terms]
93 terms (Mono lang) txt = pure $ monoTerms lang txt
94 terms (Multi lang) txt = multiterms lang txt
95 terms (MonoMulti lang) txt = terms (Multi lang) txt
96 terms (Unsupervised lang n m) txt = termsUnsupervised m' n lang txt
97 where
98 m' = maybe (newTries n txt) identity m
99 -- terms (WithList list) txt = pure . concat $ extractTermsWithList list txt
100 ------------------------------------------------------------------------
101
102 text2term :: Lang -> [Text] -> Terms
103 text2term _ [] = Terms [] Set.empty
104 text2term lang txt = Terms txt (Set.fromList $ map (stem lang) txt)
105
106 isPunctuation :: Text -> Bool
107 isPunctuation x = List.elem x $ (Text.pack . pure)
108 <$> ("!?(),;." :: String)
109
110 -- | Unsupervised ngrams extraction
111 -- language agnostic extraction
112 -- TODO: remove IO
113 -- TODO: newtype BlockText
114 termsUnsupervised :: Tries Token () -> Int -> Lang -> Text -> IO [Terms]
115 termsUnsupervised m n l =
116 pure
117 . map (text2term l)
118 . List.nub
119 . (List.filter (\l' -> List.length l' > 1))
120 . List.concat
121 . mainEleveWith m n
122 . uniText
123
124 newTries :: Int -> Text -> Tries Token ()
125 newTries n t = buildTries n (fmap toToken $ uniText t)
126
127 uniText :: Text -> [[Text]]
128 uniText = map (List.filter (not . isPunctuation))
129 . map tokenize
130 . sentences -- | TODO get sentences according to lang
131
132