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

[API][GRAPH] cosmetics to prepare next step.

parent 6d58acdd
......@@ -319,8 +319,8 @@ type GargPrivateAPI' =
type API = SwaggerAPI
:<|> FrontEndAPI
:<|> GargAPI
:<|> Get '[HTML] Html
:<|> GargAPI
-- This is the concrete monad. It needs to be used as little as possible,
-- instead, prefer GargServer, GargServerT, GargServerC.
......@@ -341,8 +341,8 @@ server env = do
-- orchestrator <- scrapyOrchestrator env
pure $ schemaUiServer swaggerDoc
:<|> frontEndServer
:<|> hoistServerWithContext (Proxy :: Proxy GargAPI) (Proxy :: Proxy AuthContext) transform serverGargAPI
:<|> serverStatic
:<|> hoistServerWithContext (Proxy :: Proxy GargAPI) (Proxy :: Proxy AuthContext) transform serverGargAPI
where
transform :: forall a. GargServerM env GargError a -> Handler a
transform = Handler . withExceptT showAsServantErr . (`runReaderT` env)
......
......@@ -24,7 +24,7 @@ Portability : POSIX
module Gargantext.Viz.Graph.API
where
import Debug.Trace (trace)
-- import Debug.Trace (trace)
import Control.Lens (set, (^.), _Just, (^?))
import Control.Monad.IO.Class (liftIO)
import Data.Maybe (Maybe(..))
......@@ -94,7 +94,7 @@ getGraph uId nId = do
graph'' <- computeGraph cId NgramsTerms repo
_ <- updateHyperdata nId (HyperdataGraph $ Just graph'')
pure graph''
pure $ trace ("salut" <> show g) $ g
pure {- $ trace (show g) $ -} g
-- TODO use Database Monad only here ?
......
......@@ -53,14 +53,14 @@ cooc2graph threshold myCooc = do
where
(as, bs) = List.unzip $ Map.keys distanceMap
n' = Set.size $ Set.fromList $ as <> bs
ClustersParams rivers level = trace ("nodesApprox: " <> show nodesApprox) $ clustersParams nodesApprox
ClustersParams rivers level = {-trace ("nodesApprox: " <> show nodesApprox) $-} clustersParams nodesApprox
partitions <- case Map.size distanceMap > 0 of
True -> trace ("level" <> show level) $ cLouvain level distanceMap
False -> panic "Text.Flow: DistanceMap is empty"
let bridgeness' = trace ("rivers: " <> show rivers) $ bridgeness rivers partitions distanceMap
let bridgeness' = {-trace ("rivers: " <> show rivers) $-} bridgeness rivers partitions distanceMap
let confluence' = confluence (Map.keys bridgeness') 3 True False
data2graph (Map.toList ti) myCooc' bridgeness' confluence' partitions
......@@ -72,14 +72,14 @@ data ClustersParams = ClustersParams { bridgness :: Double
} deriving (Show)
clustersParams :: Int -> ClustersParams
clustersParams x = ClustersParams (fromIntegral x) y
where
y | x < 100 = "0.01"
| x < 350 = "0.01"
| x < 500 = "0.01"
| x < 1000 = "0.1"
clustersParams x = ClustersParams (fromIntegral x) "0.00000001" -- y
{- where
y | x < 100 = "0.000001"
| x < 350 = "0.000001"
| x < 500 = "0.000001"
| x < 1000 = "0.000001"
| otherwise = "1"
-}
----------------------------------------------------------
-- | From data to 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