]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Text/Metrics/FrequentItemSet.hs
[SCORE] spegen quality tested, need to add test in comments.
[gargantext.git] / src / Gargantext / Text / Metrics / FrequentItemSet.hs
1 {-|
2 Module : Gargantext.Text.Metrics.FrequentItemSet
3 Description : Ngrams tools
4 Copyright : (c) CNRS, 2018
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Domain Specific Language to manage Frequent Item Set (FIS)
11
12 -}
13
14 {-# LANGUAGE NoImplicitPrelude #-}
15
16 module Gargantext.Text.Metrics.FrequentItemSet
17 ( Fis, Size(..)
18 , occ_hlcm, cooc_hlcm
19 , all, between
20 , module HLCM
21 )
22 where
23
24 import Prelude (Functor(..)) -- TODO
25 import qualified Data.Map.Strict as Map
26 import Data.Map.Strict (Map)
27 import qualified Data.Set as Set
28 import Data.Set (Set)
29 import qualified Data.Vector as V
30 import Data.Vector (Vector)
31
32 import Data.List (filter, concat)
33 import Data.Maybe (catMaybes)
34
35 import HLCM
36
37 import Gargantext.Prelude
38
39 data Size = Point Int | Segment Int Int
40
41 ------------------------------------------------------------------------
42 -- | Occurrence is Frequent Item Set of size 1
43 occ_hlcm :: Frequency -> [[Item]] -> [Fis]
44 occ_hlcm = fisWithSize (Point 1)
45
46 -- | Cooccurrence is Frequent Item Set of size 2
47 cooc_hlcm :: Frequency -> [[Item]] -> [Fis]
48 cooc_hlcm = fisWithSize (Point 2)
49
50 all :: Frequency -> [[Item]] -> [Fis]
51 all = fisWith Nothing
52
53 ------------------------------------------------------------------------
54 between :: (Int, Int) -> Frequency -> [[Item]] -> [Fis]
55 between (x,y) = fisWithSize (Segment x y)
56
57 --maximum :: Int -> Frequency -> [[Item]] -> [Fis]
58 --maximum m = between (0,m)
59
60
61 ------------------------------------------------------------------------
62 ------------------------------------------------------------------------
63 -- | Data type to type the Frequent Item Set
64 -- TODO replace List with Set in fisItemSet
65 -- be careful : risks to erase HLCM behavior
66 type Fis = Fis' Item
67 data Fis' a = Fis' { _fisCount :: Int
68 , _fisItemSet :: [a]
69 } deriving (Show)
70
71 instance Functor Fis' where
72 fmap f (Fis' c is) = Fis' c (fmap f is)
73
74 -- | Sugar from items to FIS
75 items2fis :: [Item] -> Maybe Fis
76 items2fis [] = Nothing
77 items2fis (i:is) = Just $ Fis' i is
78
79 ------------------------------------------------------------------------
80 ------------------------------------------------------------------------
81
82 fisWithSize :: Size -> Frequency -> [[Item]] -> [Fis]
83 fisWithSize n f is = case n of
84 Point n' -> fisWith (Just (\x -> length x == (n'+1) )) f is
85 Segment a b -> fisWith (Just (\x -> cond a (length x) b)) f is
86 where
87 cond a' x b' = a' <= x && x <= b'
88
89
90 fisWith :: Maybe ([Item] -> Bool) -> Frequency -> [[Item]] -> [Fis]
91 fisWith s f is = catMaybes $ map items2fis $ filter' $ runLCMmatrix is f
92 where
93 filter' = case s of
94 Nothing -> identity
95 Just fun -> filter fun
96
97 -- Here the sole purpose to take the keys as a Set is tell we do not want
98 -- duplicates.
99 fisWithSizePoly :: Ord a => Size -> Frequency -> Set a -> [[a]] -> [Fis' a]
100 fisWithSizePoly n f ks = map (fmap fromItem) . fisWithSize n f . map (map toItem)
101 where
102 ksv = V.fromList $ Set.toList ks
103 ksm = Map.fromList . flip zip [0..] $ V.toList ksv
104 toItem = (ksm Map.!)
105 fromItem = (ksv V.!)
106
107 fisWithSizePoly2 :: Ord a => Size -> Frequency -> [[a]] -> [Fis' a]
108 fisWithSizePoly2 n f is = fisWithSizePoly n f ks is
109 where
110 ks = Set.fromList $ concat is
111
112
113 ------------------------------------------------------------------------
114 ------------------------------------------------------------------------
115
116
117 --
118 ---- | /!\ indexes are not the same:
119 --
120 ---- | Index ngrams from Map
121 ----indexNgram :: Ord a => Map a Occ -> Map Index a
122 ----indexNgram m = fromList (zip [1..] (keys m))
123 --
124 ---- | Index ngrams from Map
125 ----ngramIndex :: Ord a => Map a Occ -> Map a Index
126 ----ngramIndex m = fromList (zip (keys m) [1..])
127 --
128 --indexWith :: Ord a => Map a Occ -> [a] -> [Int]
129 --indexWith m xs = unMaybe $ map (\x -> lookupIndex x m) xs
130 --
131 --indexIt :: Ord a => [[a]] -> (Map a Int, [[Int]])
132 --indexIt xs = (m, is)
133 -- where
134 -- m = sumOcc (map occ xs)
135 -- is = map (indexWith m) xs
136 --
137 --list2fis :: Ord a => FIS.Frequency -> [[a]] -> (Map a Int, [FIS.Fis])
138 --list2fis n xs = (m', fs)
139 -- where
140 -- (m, is) = indexIt xs
141 -- m' = M.filter (>50000) m
142 -- fs = FIS.all n is
143 --
144 --text2fis :: FIS.Frequency -> [Text] -> (Map Text Int, [FIS.Fis])
145 --text2fis n xs = list2fis n (map terms xs)
146 --
147 ----text2fisWith :: FIS.Size -> FIS.Frequency -> [Text] -> (Map Text Int, [FIS.Fis])
148 ----text2fisWith = undefined
149 --
150