Commit 7e65040f authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into 74-dev-frame-calc-csv-import

parents b997e0a9 62970e2e
Pipeline #2188 failed with stage
in 10 minutes and 24 seconds
## Version 0.0.4.9.1
* [FIX] Graph Screenshot
## Version 0.0.4.9
* [FEAT] Graph with order 1 and order 2 and node size
## Version 0.0.4.8.9
* BACKEND: fix psql function util without sensitive data
* FRONTEND: fix folder navigation (up link)
......
#!/bin/bash
stack install --nix --profile --test --fast --no-install-ghc --skip-ghc-check
#stack install --nix --profile --test --fast --no-install-ghc --skip-ghc-check
stack install --nix --test --no-install-ghc --skip-ghc-check
name: gargantext
version: '0.0.4.8.9'
version: '0.0.4.9.1'
synopsis: Search, map, share
description: Please see README.md
category: Data
......
......@@ -71,6 +71,7 @@ type Neighbor = Node
-- | getMaxCliques
-- TODO chose distance order
getMaxCliques :: Ord a => CliqueFilter -> Distance -> Threshold -> Map (a, a) Int -> [[a]]
getMaxCliques f d t m = map fromIndices $ getMaxCliques' t m'
where
......
......@@ -9,7 +9,6 @@ Portability : POSIX
-}
{-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
{-# LANGUAGE TypeOperators #-}
......@@ -159,13 +158,6 @@ recomputeGraph _uId nId maybeDistance = do
pure $ trace "[G.V.G.API] Graph exists, recomputing" graph'''
-- TODO use Database Monad only here ?
--computeGraph :: HasNodeError err
-- => CorpusId
-- -> Distance
-- -> NgramsType
-- -> NodeListStory
-- -> Cmd err Graph
computeGraph :: FlowCmdM env err m
=> CorpusId
-> Distance
......@@ -180,7 +172,9 @@ computeGraph cId d nt repo = do
$ mapTermListRoot [lId] nt repo
myCooc <- HashMap.filter (>1) -- Removing the hapax (ngrams with 1 cooc)
<$> getCoocByNgrams (if d == Conditional then Diagonal True else Diagonal False)
-- <$> HashMap.filterWithKey (\(x,y) _ -> x /= y)
-- <$> getCoocByNgrams (if d == Conditional then Diagonal True else Diagonal False)
<$> getCoocByNgrams (Diagonal True)
<$> groupNodesByNgrams ngs
<$> getNodesByNgramsOnlyUser cId (lIds <> [lId]) nt (HashMap.keys ngs)
......@@ -220,7 +214,6 @@ defaultGraphMetadata cId t repo gm = do
}
-- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
------------------------------------------------------------
type GraphAsyncAPI = Summary "Recompute graph"
:> "recompute"
......@@ -339,8 +332,3 @@ getGraphGexf uId nId = do
HyperdataGraphAPI { _hyperdataAPIGraph = graph } <- getGraph uId nId
pure $ addHeader "attachment; filename=graph.gexf" graph
......@@ -28,7 +28,7 @@ import qualified Data.Array.Accelerate as A
import qualified Data.Array.Accelerate.Interpreter as A
import Data.Array.Accelerate (Matrix, Elt, Shape, (:.)(..), Z(..))
import Data.Maybe (fromMaybe)
import Data.Maybe (fromMaybe, catMaybes)
import Data.Set (Set)
import qualified Data.Set as S
......@@ -69,7 +69,7 @@ map2mat sym def n m = A.fromFunction shape getData
case sym of
Triangle -> fromMaybe def (M.lookup (x,y) m)
Square -> fromMaybe (fromMaybe def $ M.lookup (y,x) m)
$ M.lookup (x, y) m
$ M.lookup (x,y) m
)
shape = (Z :. n :. n)
......@@ -93,8 +93,11 @@ fromIndex ni ns = indexConversion ni ns
indexConversion :: (Ord b, Ord k) => Map k b -> Map (k,k) a -> Map (b, b) a
indexConversion index ms = M.fromList
$ map (\((k1,k2),c) -> ( ((M.!) index k1, (M.!) index k2), c))
(M.toList ms)
$ catMaybes
$ map (\((k1,k2),c) -> ((,) <$> ((,) <$> M.lookup k1 index <*> M.lookup k2 index)
<*> Just c)
)
$ M.toList ms
---------------------------------------------------------------------------------
-------------------------------------------------------------------------------
......
This diff is collapsed.
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