2 Module : Gargantext.Core.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
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
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.
19 Source: https://en.wikipedia.org/wiki/Ngrams
23 compute occ by node of Tree
24 group occs according groups
31 {-# LANGUAGE TemplateHaskell #-}
32 {-# LANGUAGE ConstrainedClassMethods #-}
34 module Gargantext.Core.Text.Terms
39 import qualified Data.Map as Map
40 import Data.Text (Text)
41 import Data.Traversable
42 import GHC.Base (String)
43 import GHC.Generics (Generic)
44 import Gargantext.Core
45 import Gargantext.Core.Types
46 import Gargantext.Core.Flow.Types
47 import Gargantext.Prelude
48 import Gargantext.Core.Text (sentences, HasText(..))
49 import Gargantext.Core.Text.Terms.Eleve (mainEleveWith, Tries, Token, buildTries, toToken)
50 import Gargantext.Database.Schema.Ngrams (Ngrams(..), NgramsType(..))
51 import Gargantext.Core.Text.Terms.Mono (monoTerms)
52 import Gargantext.Database.Prelude (Cmd)
53 import Gargantext.Core.Text.Terms.Mono.Stem (stem)
54 import Gargantext.Core.Text.Terms.Mono.Token.En (tokenize)
55 import Gargantext.Core.Text.Terms.Multi (multiterms)
56 import qualified Data.List as List
57 import qualified Data.Set as Set
58 import qualified Data.Text as Text
61 = Mono { _tt_lang :: !lang }
62 | Multi { _tt_lang :: !lang }
63 | MonoMulti { _tt_lang :: !lang }
64 | Unsupervised { _tt_lang :: !lang
65 , _tt_windowSize :: !Int
66 , _tt_ngramsSize :: !Int
67 , _tt_model :: !(Maybe (Tries Token ()))
72 --group :: [Text] -> [Text]
76 -- map (filter (\t -> not . elem t)) $
77 ------------------------------------------------------------------------
78 -- | Sugar to extract terms from text (hiddeng mapM from end user).
79 --extractTerms :: Traversable t => TermType Lang -> t Text -> IO (t [Terms])
80 extractTerms :: TermType Lang -> [Text] -> IO [[Terms]]
82 extractTerms (Unsupervised l n s m) xs = mapM (terms (Unsupervised l n s (Just m'))) xs
86 Nothing -> newTries n (Text.intercalate " " xs)
88 extractTerms termTypeLang xs = mapM (terms termTypeLang) xs
91 ------------------------------------------------------------------------
96 withLang (Unsupervised l n s m) ns = Unsupervised l n s m'
99 Nothing -> -- trace ("buildTries here" :: String)
100 Just $ buildTries n ( fmap toToken
102 $ Text.intercalate " . "
108 ------------------------------------------------------------------------
111 class ExtractNgramsT h
113 extractNgramsT :: HasText h
116 -> Cmd err (Map Ngrams (Map NgramsType Int))
118 filterNgramsT :: Int -> Map Ngrams (Map NgramsType Int)
119 -> Map Ngrams (Map NgramsType Int)
120 filterNgramsT s ms = Map.fromList $ map (\a -> filter' s a) $ Map.toList ms
122 filter' s' (ng@(Ngrams t n),y) = case (Text.length t) < s' of
124 False -> (Ngrams (Text.take s' t) n , y)
127 -- =======================================================
131 -- Multi : multi terms
132 -- MonoMulti : mono and multi
133 -- TODO : multi terms should exclude mono (intersection is not empty yet)
134 terms :: TermType Lang -> Text -> IO [Terms]
135 terms (Mono lang) txt = pure $ monoTerms lang txt
136 terms (Multi lang) txt = multiterms lang txt
137 terms (MonoMulti lang) txt = terms (Multi lang) txt
138 terms (Unsupervised lang n s m) txt = termsUnsupervised (Unsupervised lang n s (Just m')) txt
140 m' = maybe (newTries n txt) identity m
141 -- terms (WithList list) txt = pure . concat $ extractTermsWithList list txt
142 ------------------------------------------------------------------------
144 text2term :: Lang -> [Text] -> Terms
145 text2term _ [] = Terms [] Set.empty
146 text2term lang txt = Terms txt (Set.fromList $ map (stem lang) txt)
148 isPunctuation :: Text -> Bool
149 isPunctuation x = List.elem x $ (Text.pack . pure)
150 <$> ("!?(),;." :: String)
152 -- | Unsupervised ngrams extraction
153 -- language agnostic extraction
155 -- TODO: newtype BlockText
157 type WindowSize = Int
158 type MinNgramSize = Int
160 termsUnsupervised :: TermType Lang -> Text -> IO [Terms]
161 termsUnsupervised (Unsupervised l n s m) =
165 . (List.filter (\l' -> List.length l' >= s))
167 . mainEleveWith (maybe (panic "no model") identity m) n
169 termsUnsupervised _ = undefined
171 newTries :: Int -> Text -> Tries Token ()
172 newTries n t = buildTries n (fmap toToken $ uniText t)
174 -- | TODO removing long terms > 24
175 uniText :: Text -> [[Text]]
176 uniText = map (List.filter (not . isPunctuation))
178 . sentences -- TODO get sentences according to lang