Commit 6050f41e authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'criterion-example'

parents 4b8b45aa d70b3a4d
......@@ -4,13 +4,14 @@ module Main where
import Data.Set as Set
import Data.String.Conversions (cs)
import System.Environment (getArgs)
import System.Environment (getArgs, withArgs)
import Data.Text (Text)
import Graph.BAC.Clustering
import Graph.BAC.ProxemyOptim
import Graph.BAC.ProxemyOptim
import Graph.FGL
import Graph.Tools.Import
import Graph.Types
import Prelude (String)
import Protolude
import qualified Data.IntMap as Dict
......@@ -20,16 +21,19 @@ import qualified Eigen.SparseMatrix as SMatrix
import qualified Prelude as Prelude
import qualified Data.Graph.Inductive.PatriciaTree as DGIP
import Criterion
import Criterion.Main
setupEnv :: [String] -> IO (Dict a, Graph () ())
setupEnv [fp] = getUnlabGraph (WithFile fp)
setupEnv _ = getUnlabGraph Random
main :: IO ()
main = do
fp <- getArgs
(m,g) <- case fp of
[] -> getUnlabGraph Random
[fp'] -> getUnlabGraph (WithFile fp')
-- Profiling should start here
let
result = withG g (parts . (clusteringOptim 3 Conf))
-- Profiling should end here
print (result)
withArgs [] $
defaultMain
[ env (snd <$> setupEnv fp) $ \ ~g ->
bench "bench" (nf (\ x -> withG x (parts . clusteringOptim 3 Conf)) g)
]
......@@ -85,6 +85,7 @@ executable gargantext-graph-exe
, cassava
, cereal
, containers
, criterion
, eigen
, fgl
, gargantext-graph
......
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