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

[COMPILE] ok

parent bdc1123b
......@@ -4,7 +4,7 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 94b44a88c27580d41ae4220e3a3c8578c4f72d98ec3ba3638161723463c03df8
-- hash: 2529152eda79b364f7b62e5d9eaf053e8f4e54488749bd83614d515e92c44d26
name: gargantext-graph
version: 0.1.0.0
......@@ -57,7 +57,9 @@ library
, lens
, pretty-simple
, protolude
, reflection
, singletons
, string-conversions
, text
, vector
default-language: Haskell2010
......@@ -86,7 +88,9 @@ executable gargantext-graph-exe
, lens
, pretty-simple
, protolude
, reflection
, singletons
, string-conversions
, text
, vector
default-language: Haskell2010
......@@ -116,7 +120,9 @@ test-suite gargantext-graph-test
, lens
, pretty-simple
, protolude
, reflection
, singletons
, string-conversions
, text
, vector
default-language: Haskell2010
......@@ -21,22 +21,24 @@ description: Please see the README on GitHub at <https://github.com/gith
dependencies:
- accelerate
- accelerate-utility
- accelerate-arithmetic
- accelerate-utility
- base >= 4.7 && < 5
- bytestring
- cassava
- cereal # (IGraph)
- containers
- eigen
- fgl
- haskell-igraph >= 0.6.0
- lens
- pretty-simple
- protolude
- reflection
- singletons
- string-conversions
- text
- vector
- eigen
default-extensions:
- DataKinds
......
......@@ -22,6 +22,8 @@ Gaume.
TypeOperators #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
module Graph.BAC.ProxemyOptim
where
......@@ -31,6 +33,7 @@ import Data.Maybe (isJust)
import Data.Proxy (Proxy(Proxy))
import GHC.TypeLits (KnownNat, Nat, SomeNat(SomeNat), type(+), natVal, sameNat, someNatVal)
import Data.Reflection
--import Debug.SimpleReflect
import Data.Map (Map)
import Graph.FGL
......@@ -47,6 +50,7 @@ import qualified Data.Map as Map
import qualified Data.Vector.Storable as VS
import qualified Data.Vector as V
import qualified Eigen.SparseMatrix as SMatrix
import qualified Prelude as Prelude
-- | Main Types
type Length = Int
......@@ -60,6 +64,24 @@ type Graph a b = DGI.Gr a b
-- | A finite Graph is a Graph whose number of Nodes is known
data FiniteGraph (n :: Nat) a b = FiniteGraph (Graph a b)
instance (Show a, Show b) => Show (FiniteGraph n a b) where
show (FiniteGraph g) = Prelude.show g
buildFiniteGraph :: Proxy n -> Graph a b -> FiniteGraph n a b
buildFiniteGraph _ g = FiniteGraph g
withG :: (Show a, Show b)
=> Graph a b
-> (forall n. KnownNat n => FiniteGraph n a b -> r)
-> r
withG g f = reifyNat (fromIntegral $ length $ nodes g) $ \n -> f (buildFiniteGraph n g)
-- ∀ x. P x -> ∃ x. P x
data T a b where
T :: forall n a b. KnownNat n => Proxy n -> FiniteGraph n a b -> T a b
......@@ -157,14 +179,14 @@ matconf a p = symmetry $ toMatrix confmat
vcount = natToInt @n
degs = sumWith Colonne identity a
sumdeg = VS.sum degs
confmat = SMatrix.imap (\x y v -> if x < y
then let
prox_y_x_length = v
prox_y_x_infini = ((VS.!) degs x) / sumdeg
in (prox_y_x_length - prox_y_x_infini)
/ (prox_y_x_length + prox_y_x_infini)
else 0
) p
confmat = SMatrix.imap (\x y v -> if x < y
then let
prox_y_x_length = v
prox_y_x_infini = ((VS.!) degs x) / sumdeg
in (prox_y_x_length - prox_y_x_infini)
/ (prox_y_x_length + prox_y_x_infini)
else 0
) p
symmetry :: KnownNat n => DenseMatrix n -> DenseMatrix n
symmetry m = DMatrix.imap (\x y v -> if x < y then v else DMatrix.unsafeCoeff y x m) m
......@@ -183,25 +205,29 @@ matmod fg = symmetry $ toMatrix modmat
) a
---------------------------------------------------------------
type UnsortedEdges = [((Node,Node), Double)]
type SortedEdges = [((Node,Node), Double)]
edges_confluence :: KnownNat n
edges_confluence :: forall n a b. KnownNat n
=> Length
-> FiniteGraph n a b
-> AdjacencyMatrix n
-> AdjacencyMatrix n
-> TransitionMatrix n
-> UnsortedEdges
edges_confluence = undefined
edges_confluence l fg am tm = []
where
vcount = natToInt @n
degs = sumWith Colonne identity am
sumdeg = VS.sum degs
type UnsortedEdges = [((Node,Node), Double)]
type SortedEdges = [((Node,Node), Double)]
sort_edges :: Int
-> UnsortedEdges
-> SortedEdges
sort_edges = undefined
---------------------------------------------------------------
make_clust_part :: KnownNat n
=> SortedEdges
-> SimilarityMatrix n
......@@ -213,13 +239,8 @@ make_clust_over :: KnownNat n
-> StrictClustering a
-> OverlapsClustering a
make_clust_over = undefined
---------------------------------------------------------------
dim :: KnownNat n
=> FiniteGraph n a b
-> Dim n
dim = undefined
---------------------------------------------------------------
clusteringOptim :: forall n a b. KnownNat n
=> Length
-> FiniteGraph n a b
......
main :: IO ()
main = putStrLn "Test suite not yet implemented"
{-# LANGUAGE NoImplicitPrelude #-}
import Data.String.Conversions (cs)
import Data.Text (Text)
import Graph.BAC.ProxemyOptim
import Graph.FGL
import Protolude
import Prelude (String)
import qualified Eigen.SparseMatrix as SMatrix
import qualified Prelude as Prelude
edges_test :: [(Int,Int)]
edges_test=[(0,1),(0,2),(0,4),(0,5),(0,3),(0,6)
,(1,2),(1,3),(2,3),(4,5),(4,6),(5,6)
,(7,8),(7,3),(7,4),(8,2),(8,5)
]
main_test :: IO ()
main_test = do
let
g :: Graph () ()
g = mkGraphUfromEdges edges_test
n = length $ nodes g
{-
a :: KnownNat n => AdjacencyMatrix n
a = adjacent g' False
-}
print $ withG g Prelude.show -- a -- $ SMatrix.getRows a
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