Commit cdac7ca4 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Fun] ConfMat

parent b99fe650
{-# LANGUAGE NoImplicitPrelude #-}
module Main where module Main where
import Graph.Tools import Graph.Tools
......
...@@ -4,7 +4,7 @@ cabal-version: 1.12 ...@@ -4,7 +4,7 @@ cabal-version: 1.12
-- --
-- see: https://github.com/sol/hpack -- see: https://github.com/sol/hpack
-- --
-- hash: 6c4e06602da9033a6525639aa2d86c9093f65dd779b919115c4f39ef319caeba -- hash: 94b44a88c27580d41ae4220e3a3c8578c4f72d98ec3ba3638161723463c03df8
name: gargantext-graph name: gargantext-graph
version: 0.1.0.0 version: 0.1.0.0
...@@ -41,7 +41,7 @@ library ...@@ -41,7 +41,7 @@ library
Paths_gargantext_graph Paths_gargantext_graph
hs-source-dirs: hs-source-dirs:
src src
default-extensions: NoImplicitPrelude DataKinds FlexibleInstances OverloadedStrings default-extensions: DataKinds FlexibleInstances OverloadedStrings
build-depends: build-depends:
accelerate accelerate
, accelerate-arithmetic , accelerate-arithmetic
...@@ -68,7 +68,7 @@ executable gargantext-graph-exe ...@@ -68,7 +68,7 @@ executable gargantext-graph-exe
Paths_gargantext_graph Paths_gargantext_graph
hs-source-dirs: hs-source-dirs:
app app
default-extensions: NoImplicitPrelude DataKinds FlexibleInstances OverloadedStrings default-extensions: DataKinds FlexibleInstances OverloadedStrings
ghc-options: -O2 -threaded -rtsopts -with-rtsopts=-N -fprof-auto ghc-options: -O2 -threaded -rtsopts -with-rtsopts=-N -fprof-auto
build-depends: build-depends:
accelerate accelerate
...@@ -98,7 +98,7 @@ test-suite gargantext-graph-test ...@@ -98,7 +98,7 @@ test-suite gargantext-graph-test
Paths_gargantext_graph Paths_gargantext_graph
hs-source-dirs: hs-source-dirs:
test test
default-extensions: NoImplicitPrelude DataKinds FlexibleInstances OverloadedStrings default-extensions: DataKinds FlexibleInstances OverloadedStrings
ghc-options: -threaded -rtsopts -with-rtsopts=-N ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends: build-depends:
accelerate accelerate
......
...@@ -39,7 +39,6 @@ dependencies: ...@@ -39,7 +39,6 @@ dependencies:
- eigen - eigen
default-extensions: default-extensions:
- NoImplicitPrelude
- DataKinds - DataKinds
- FlexibleInstances - FlexibleInstances
- OverloadedStrings - OverloadedStrings
......
...@@ -27,6 +27,7 @@ Implementation use Accelerate library which enables GPU and CPU computation: ...@@ -27,6 +27,7 @@ Implementation use Accelerate library which enables GPU and CPU computation:
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Data.Array.Accelerate.Utils module Data.Array.Accelerate.Utils
where where
......
...@@ -11,6 +11,7 @@ POK: Parts Overlap Kern ...@@ -11,6 +11,7 @@ POK: Parts Overlap Kern
-} -}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.BAC.Clustering module Graph.BAC.Clustering
where where
......
...@@ -13,6 +13,8 @@ Références: ...@@ -13,6 +13,8 @@ Références:
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.BAC.Proxemy module Graph.BAC.Proxemy
where where
......
...@@ -6,10 +6,10 @@ Maintainer : team@gargantext.org ...@@ -6,10 +6,10 @@ Maintainer : team@gargantext.org
Stability : experimental Stability : experimental
Portability : POSIX Portability : POSIX
Références: Confluence for Graph Clustering, B. Gaume and A. Delanoë
- Bruno Gaume, Karine Duvignau, Emmanuel Navarro, Yann Desalle, Hintat Cheung, et al.. Skillex: a graph-based lexical score for measuring the semantic efficiency of used verbs by human subjects describing actions. Revue TAL, Association pour le Traitement Automatique des Langues, 2016, Revue TAL : numéro spécial sur Traitement Automatique des Langues et Sciences Cognitives (55-3), 55 (3), ⟨https://www.atala.org/-Cognitive-Issues-in-Natural-⟩. ⟨hal-01320416⟩
- Implémentation Python [Lien]() Code written in Haskell by A. Delanoë from Python Specifications by B.
Gaume.
-} -}
...@@ -20,6 +20,8 @@ Références: ...@@ -20,6 +20,8 @@ Références:
ScopedTypeVariables, ScopedTypeVariables,
StandaloneDeriving, StandaloneDeriving,
TypeOperators #-} TypeOperators #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.BAC.ProxemyOptim module Graph.BAC.ProxemyOptim
where where
...@@ -34,9 +36,10 @@ import Data.Map (Map) ...@@ -34,9 +36,10 @@ import Data.Map (Map)
import Graph.FGL import Graph.FGL
import Protolude hiding (sum, natVal) import Protolude hiding (sum, natVal)
import qualified Eigen.Matrix as DenseMatrix import qualified Eigen.Matrix as DenseMatrix
import Eigen.SparseMatrix (SparseMatrix, SparseMatrixXd) import Eigen.SparseMatrix (SparseMatrix, SparseMatrixXd, (!), toMatrix, _unsafeCoeff)
import Eigen.Internal (CTriplet(..), Elem(..), toC, fromC, C(..)) import Eigen.Internal (CTriplet(..), Elem(..), toC, fromC, C(..), natToInt, Row(..), Col(..))
import Eigen.Matrix (sum) import Eigen.Matrix (sum, unsafeCoeff)
import qualified Eigen.Matrix as DMatrix
import qualified Data.Graph.Inductive as DGI import qualified Data.Graph.Inductive as DGI
import qualified Data.Graph.Inductive.PatriciaTree as DGIP import qualified Data.Graph.Inductive.PatriciaTree as DGIP
import qualified Data.List as List import qualified Data.List as List
...@@ -78,6 +81,7 @@ tab g = do ...@@ -78,6 +81,7 @@ tab g = do
type DenseMatrix n = DenseMatrix.Matrix n n Double type DenseMatrix n = DenseMatrix.Matrix n n Double
type AdjacencyMatrix n = SparseMatrix n n Double type AdjacencyMatrix n = SparseMatrix n n Double
type TransitionMatrix n = SparseMatrix n n Double type TransitionMatrix n = SparseMatrix n n Double
type ProxemyMatrix n = SparseMatrix n n Double
type ConfluenceMatrix n = DenseMatrix n type ConfluenceMatrix n = DenseMatrix n
type ModularityMatrix n = DenseMatrix n type ModularityMatrix n = DenseMatrix n
...@@ -124,11 +128,8 @@ transition m = SMatrix.mul m (sumWith (\s -> 1 / s) m) ...@@ -124,11 +128,8 @@ transition m = SMatrix.mul m (sumWith (\s -> 1 / s) m)
sumWith :: ( Elem a sumWith :: ( Elem a
, Elem t , Elem t
, KnownNat n1 , KnownNat n
, KnownNat m1 ) => (t -> a) -> SparseMatrix n n t -> SparseMatrix n n a
, KnownNat n2
, KnownNat m2
) => (t -> a) -> SparseMatrix n2 m2 t -> SparseMatrix n1 m1 a
sumWith f m = SMatrix.fromVector sumWith f m = SMatrix.fromVector
$ VS.fromList $ VS.fromList
$ List.zipWith (\i v -> CTriplet i 1 (toC (f v))) [1..] $ List.zipWith (\i v -> CTriplet i 1 (toC (f v))) [1..]
...@@ -140,17 +141,29 @@ sumWith f m = SMatrix.fromVector ...@@ -140,17 +141,29 @@ sumWith f m = SMatrix.fromVector
proxemie :: KnownNat n proxemie :: KnownNat n
=> Length => Length
-> TransitionMatrix n -> TransitionMatrix n
-> TransitionMatrix n -> ProxemyMatrix n
proxemie l m = case l < 1 of proxemie l m = case l < 1 of
True -> panic "Length has to be >= 1" True -> panic "Length has to be >= 1"
False -> foldl' (\m' _-> SMatrix.mul m' m) m [1 .. (l :: Int)] False -> foldl' (\m' _-> SMatrix.mul m' m) m [1 .. (l :: Int)]
--------------------------------------------------------------- ---------------------------------------------------------------
matconf :: KnownNat n => AdjacencyMatrix n -> TransitionMatrix n -> ConfluenceMatrix n matconf :: forall n. KnownNat n => AdjacencyMatrix n -> ProxemyMatrix n -> ConfluenceMatrix n
matconf a t = undefined {- do matconf a p = symmetry $ toMatrix confmat
let vcount = SMatrix.cols_ a where
-} vcount = natToInt @n
degs = sumWith identity a
sumdeg = sum (toMatrix degs)
symmetry m = DMatrix.imap (\x y v -> if x < y then v else DMatrix.unsafeCoeff y x m) m
confmat = SMatrix.imap (\x y v -> if x < y
then let
prox_y_x_length = v
prox_y_x_infini = (_unsafeCoeff x 1 degs) / sumdeg
in (prox_y_x_length - prox_y_x_infini)
/ (prox_y_x_length + prox_y_x_infini)
else 0
) p
matmod :: KnownNat n => FiniteGraph n a b -> ModularityMatrix n matmod :: KnownNat n => FiniteGraph n a b -> ModularityMatrix n
matmod = undefined matmod = undefined
......
...@@ -12,6 +12,7 @@ POK: Parts Overlap Kern ...@@ -12,6 +12,7 @@ POK: Parts Overlap Kern
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.BAC.Scores module Graph.BAC.Scores
where where
......
...@@ -10,6 +10,7 @@ Reference: Article POK de QuaC de G ...@@ -10,6 +10,7 @@ Reference: Article POK de QuaC de G
POK: Parts Overlap Kern POK: Parts Overlap Kern
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.BAC.Test module Graph.BAC.Test
where where
......
...@@ -10,6 +10,7 @@ Portability : POSIX ...@@ -10,6 +10,7 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.BAC.Types module Graph.BAC.Types
where where
......
...@@ -12,6 +12,7 @@ Main DGI funs/types to ease portability with IGraph. ...@@ -12,6 +12,7 @@ Main DGI funs/types to ease portability with IGraph.
{-# LANGUAGE ConstrainedClassMethods #-} {-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.FGL where module Graph.FGL where
......
...@@ -13,6 +13,7 @@ Reference: ...@@ -13,6 +13,7 @@ Reference:
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.IGraph where module Graph.IGraph where
......
...@@ -11,6 +11,7 @@ Portability : POSIX ...@@ -11,6 +11,7 @@ Portability : POSIX
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Graph.Tools where module Graph.Tools where
......
...@@ -32,7 +32,8 @@ allow-newer: true ...@@ -32,7 +32,8 @@ allow-newer: true
# - wai # - wai
packages: packages:
- . - .
# Dependency packages to be pulled from upstream that are not in the resolver. - '../eigen/'
# Dependency packages to be pulled from upstream that are not in the resolver.
# These entries can reference officially published versions as well as # These entries can reference officially published versions as well as
# forks / in-progress versions pinned to a git hash. For example: # forks / in-progress versions pinned to a git hash. For example:
# #
...@@ -44,7 +45,7 @@ extra-deps: ...@@ -44,7 +45,7 @@ extra-deps:
- git: https://gitlab.iscpif.fr/anoe/accelerate-utility.git - git: https://gitlab.iscpif.fr/anoe/accelerate-utility.git
commit: 83ada76e78ac10d9559af8ed6bd4064ec81308e4 commit: 83ada76e78ac10d9559af8ed6bd4064ec81308e4
- accelerate-arithmetic-1.0.0.1@sha256:555639232aa5cad411e89247b27871d09352b987a754230a288c690b6de6d888,2096 - accelerate-arithmetic-1.0.0.1@sha256:555639232aa5cad411e89247b27871d09352b987a754230a288c690b6de6d888,2096
- eigen-3.3.7.0@sha256:7c24a86426b238e02ba0ac2179cc44997518b443a13828ed7a791fe49a6dffa5,82060 # - eigen-3.3.7.0@sha256:7c24a86426b238e02ba0ac2179cc44997518b443a13828ed7a791fe49a6dffa5,82060
# Override default flag values for local packages and extra-deps # Override default flag values for local packages and extra-deps
......
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