Commit 4a25b912 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[TYPE] semantics, renaming

parent 17f1d540
...@@ -91,7 +91,7 @@ filterListWithRootHashMap lt m = snd <$> HM.filter isMapTerm m ...@@ -91,7 +91,7 @@ filterListWithRootHashMap lt m = snd <$> HM.filter isMapTerm m
isMapTerm (l, maybeRoot) = case maybeRoot of isMapTerm (l, maybeRoot) = case maybeRoot of
Nothing -> l == lt Nothing -> l == lt
Just r -> case HM.lookup r m of Just r -> case HM.lookup r m of
Nothing -> panic $ "Garg.API.Ngrams.Tools: filterWithRoot, unknown key: " <> unNgramsTerm r Nothing -> panic $ "[Garg.API.Ngrams.Tools] filterWithRoot, unknown key: " <> unNgramsTerm r
Just (l',_) -> l' == lt Just (l',_) -> l' == lt
filterListWithRoot :: ListType filterListWithRoot :: ListType
...@@ -102,7 +102,7 @@ filterListWithRoot lt m = snd <$> HM.filter isMapTerm m ...@@ -102,7 +102,7 @@ filterListWithRoot lt m = snd <$> HM.filter isMapTerm m
isMapTerm (l, maybeRoot) = case maybeRoot of isMapTerm (l, maybeRoot) = case maybeRoot of
Nothing -> l == lt Nothing -> l == lt
Just r -> case HM.lookup r m of Just r -> case HM.lookup r m of
Nothing -> panic $ "Garg.API.Ngrams.Tools: filterWithRoot, unknown key: " <> unNgramsTerm r Nothing -> panic $ "[Garg.API.Ngrams.Tools] filterWithRoot, unknown key: " <> unNgramsTerm r
Just (l',_) -> l' == lt Just (l',_) -> l' == lt
groupNodesByNgrams :: ( At root_map groupNodesByNgrams :: ( At root_map
......
...@@ -112,7 +112,7 @@ ex_cooc_mat :: IO (Map Label Index, Matrix Int, Matrix Double, (DAA.Vector Gener ...@@ -112,7 +112,7 @@ ex_cooc_mat :: IO (Map Label Index, Matrix Int, Matrix Double, (DAA.Vector Gener
ex_cooc_mat = do ex_cooc_mat = do
m <- ex_cooc m <- ex_cooc
let (ti,_) = createIndices m let (ti,_) = createIndices m
let mat_cooc = cooc2mat Triangular ti m let mat_cooc = cooc2mat Triangle ti m
pure ( ti pure ( ti
, mat_cooc , mat_cooc
, incExcSpeGen_proba mat_cooc , incExcSpeGen_proba mat_cooc
...@@ -123,7 +123,7 @@ ex_incExcSpeGen :: IO ([(Label, Double)], [(Label, Double)]) ...@@ -123,7 +123,7 @@ ex_incExcSpeGen :: IO ([(Label, Double)], [(Label, Double)])
ex_incExcSpeGen = incExcSpeGen_sorted <$> ex_cooc ex_incExcSpeGen = incExcSpeGen_sorted <$> ex_cooc
incExcSpeGen_sorted :: Ord t => Map (t,t) Int -> ([(t,Double)],[(t,Double)]) incExcSpeGen_sorted :: Ord t => Map (t,t) Int -> ([(t,Double)],[(t,Double)])
incExcSpeGen_sorted m = both ordonne (incExcSpeGen $ cooc2mat Triangular ti m) incExcSpeGen_sorted m = both ordonne (incExcSpeGen $ cooc2mat Triangle ti m)
where where
(ti,fi) = createIndices m (ti,fi) = createIndices m
ordonne x = sortWith (Down . snd) ordonne x = sortWith (Down . snd)
......
...@@ -70,7 +70,7 @@ localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [ ...@@ -70,7 +70,7 @@ localMetrics' m = Map.fromList $ zipWith (\(_,t) (inc,spe) -> (t, Vec.fromList [
scores scores
where where
(ti, fi) = createIndices m (ti, fi) = createIndices m
(is, ss) = incExcSpeGen $ cooc2mat Triangular ti m (is, ss) = incExcSpeGen $ cooc2mat Triangle ti m
scores = DAA.toList scores = DAA.toList
$ DAA.run $ DAA.run
$ DAA.zip (DAA.use is) (DAA.use ss) $ DAA.zip (DAA.use is) (DAA.use ss)
...@@ -82,7 +82,7 @@ scored' :: Ord t => Map (t,t) Int -> [Scored t] ...@@ -82,7 +82,7 @@ scored' :: Ord t => Map (t,t) Int -> [Scored t]
scored' m = zipWith (\(_,t) (inc,spe) -> Scored t inc spe) (Map.toList fi) scores scored' m = zipWith (\(_,t) (inc,spe) -> Scored t inc spe) (Map.toList fi) scores
where where
(ti, fi) = createIndices m (ti, fi) = createIndices m
(is, ss) = incExcSpeGen $ cooc2mat Triangular ti m (is, ss) = incExcSpeGen $ cooc2mat Triangle ti m
scores = DAA.toList scores = DAA.toList
$ DAA.run $ DAA.run
$ DAA.zip (DAA.use is) (DAA.use ss) $ DAA.zip (DAA.use is) (DAA.use ss)
......
...@@ -60,17 +60,17 @@ cooc2mat sym ti m = map2mat sym 0 n idx ...@@ -60,17 +60,17 @@ cooc2mat sym ti m = map2mat sym 0 n idx
n = M.size ti n = M.size ti
idx = toIndex ti m -- it is important to make sure that toIndex is ran only once. idx = toIndex ti m -- it is important to make sure that toIndex is ran only once.
data MatrixShape = Triangular | Square data MatrixShape = Triangle | Square
map2mat :: Elt a => MatrixShape -> a -> Int -> Map (Index, Index) a -> Matrix a map2mat :: Elt a => MatrixShape -> a -> Int -> Map (Index, Index) a -> Matrix a
map2mat sym def n m = A.fromFunction shape getData map2mat sym def n m = A.fromFunction shape getData
where where
getData = (\(Z :. x :. y) -> getData = (\(Z :. x :. y) ->
case sym of case sym of
Triangular -> fromMaybe def (M.lookup (x,y) m) Triangle -> fromMaybe def (M.lookup (x,y) m)
Square -> fromMaybe (fromMaybe def $ M.lookup (y,x) m) Square -> fromMaybe (fromMaybe def $ M.lookup (y,x) m)
$ M.lookup (x, y) m $ M.lookup (x, y) m
) )
shape = (Z :. n :. n) shape = (Z :. n :. n)
mat2map :: (Elt a, Shape (Z :. Index)) => mat2map :: (Elt a, Shape (Z :. Index)) =>
......
...@@ -57,8 +57,8 @@ cooc2graph' distance threshold myCooc ...@@ -57,8 +57,8 @@ cooc2graph' distance threshold myCooc
$ mat2map $ mat2map
$ measure distance $ measure distance
$ case distance of $ case distance of
Conditional -> map2mat Triangular 0 tiSize Conditional -> map2mat Triangle 0 tiSize
Distributional -> map2mat Square 0 tiSize Distributional -> map2mat Square 0 tiSize
$ Map.filter (> 1) myCooc' $ Map.filter (> 1) myCooc'
where where
...@@ -85,7 +85,7 @@ cooc2graph'' distance threshold myCooc = neighbouMap ...@@ -85,7 +85,7 @@ cooc2graph'' distance threshold myCooc = neighbouMap
where where
(ti, _) = createIndices myCooc (ti, _) = createIndices myCooc
myCooc' = toIndex ti myCooc myCooc' = toIndex ti myCooc
matCooc = map2mat Triangular 0 (Map.size ti) $ Map.filter (> 1) myCooc' matCooc = map2mat Triangle 0 (Map.size ti) $ Map.filter (> 1) myCooc'
distanceMat = measure distance matCooc distanceMat = measure distance matCooc
neighbouMap = filterByNeighbours threshold neighbouMap = filterByNeighbours threshold
$ mat2map distanceMat $ mat2map distanceMat
...@@ -125,7 +125,7 @@ cooc2graphWith' doPartitions distance threshold myCooc = do ...@@ -125,7 +125,7 @@ cooc2graphWith' doPartitions distance threshold myCooc = do
tiSize = Map.size ti tiSize = Map.size ti
myCooc' = toIndex ti theMatrix myCooc' = toIndex ti theMatrix
matCooc = case distance of -- Shape of the Matrix matCooc = case distance of -- Shape of the Matrix
Conditional -> map2mat Triangular 0 tiSize Conditional -> map2mat Triangle 0 tiSize
Distributional -> map2mat Square 0 tiSize Distributional -> map2mat Square 0 tiSize
$ case distance of -- Removing the Diagonal ? $ case distance of -- Removing the Diagonal ?
Conditional -> Map.filterWithKey (\(a,b) _ -> a /= b) Conditional -> Map.filterWithKey (\(a,b) _ -> a /= b)
......
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