[API] remove POST for phylo

This wasn't wrapped in worker and could result in overloading the
server.

It seems it's not used by the frontend (only GET endpoint is used).
parent 4dddd778
......@@ -4,7 +4,6 @@ module Gargantext.API.Routes.Named.Viz (
-- * Routes types
PhyloAPI(..)
, GetPhylo(..)
, PostPhylo(..)
, GraphAPI(..)
, GraphAsyncAPI(..)
, GraphVersionsAPI(..)
......@@ -31,7 +30,6 @@ import Servant.XML.Conduit (XML)
data PhyloAPI mode = PhyloAPI
{ getPhyloEp :: mode :- Summary "Phylo API" :> NamedRoutes GetPhylo
, postPhyloEp :: mode :- NamedRoutes PostPhylo
} deriving Generic
......@@ -43,9 +41,9 @@ newtype GetPhylo mode = GetPhylo
} deriving Generic
newtype PostPhylo mode = PostPhylo
{ postPhyloByListIdEp :: mode :- QueryParam "listId" ListId :> (Post '[JSON] NodeId)
} deriving Generic
-- newtype PostPhylo mode = PostPhylo
-- { postPhyloByListIdEp :: mode :- QueryParam "listId" ListId :> (Post '[JSON] NodeId)
-- } deriving Generic
-- | There is no Delete specific API for Graph since it can be deleted
......
......@@ -26,14 +26,12 @@ import Gargantext.API.Routes.Named.Viz qualified as Named
import Gargantext.API.Viz.Types
import Gargantext.Core.Types.Phylo (GraphData(..))
import Gargantext.Core.Viz.LegacyPhylo hiding (Phylo(..))
import Gargantext.Core.Viz.Phylo (PhyloConfig(..), defaultConfig, _phylo_param, _phyloParam_config)
import Gargantext.Core.Viz.Phylo (PhyloConfig(..), _phylo_param, _phyloParam_config)
import Gargantext.Core.Viz.Phylo.API.Tools
import Gargantext.Database.Prelude
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..))
import Gargantext.Database.Query.Table.Node (getClosestParentIdByType, defaultList)
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Prelude
import Servant
import Servant.Server.Generic (AsServerT)
......@@ -42,7 +40,6 @@ import Web.HttpApiData (readTextData)
phyloAPI :: IsGargServer err env m => PhyloId -> Named.PhyloAPI (AsServerT m)
phyloAPI n = Named.PhyloAPI
{ getPhyloEp = getPhylo n
, postPhyloEp = postPhylo n
}
-- :<|> putPhylo n
-- :<|> deletePhylo n
......@@ -94,35 +91,6 @@ getPhyloDataJson phyloId = do
-- pure (SVG p)
-- FIXME(adn) This handler mixes DB reads with updates outside of the same
-- transaction, due to the call to 'flowPhyloAPI' in the middle.
postPhylo :: IsGargServer err env m => PhyloId -> Named.PostPhylo (AsServerT m)
postPhylo phyloId = Named.PostPhylo $ \_lId -> do
-- TODO get Reader settings
-- s <- ask
-- let
-- _vrs = Just ("1" :: Text)
-- _sft = Just (Software "Gargantext" "4")
-- _prm = initPhyloParam vrs sft (Just q)
corpusId <- runDBQuery $ getClosestParentIdByType phyloId NodeCorpus
-- Being the first time we ask for the Phylo, there is no historical data
-- available about computing time, so we pass 'Nothing'.
phy <- flowPhyloAPI defaultConfig Nothing (fromMaybe (panicTrace "[G.C.V.P.API] no corpus ID found") corpusId) -- params
-- phyloId <- insertNodes [node NodePhylo "Phylo" (HyperdataPhylo Nothing (Just phy)) (Just corpusId) userId]
_ <- runDBTx $ updateHyperdata phyloId (HyperdataPhylo Nothing (Just phy))
pure phyloId
------------------------------------------------------------------------
-- | DELETE Phylo == delete a node
------------------------------------------------------------------------
------------------------------------------------------------------------
{-
type PutPhylo = (Put '[JSON] Phylo )
--putPhylo :: PhyloId -> Maybe ListId -> PhyloQueryBuild -> Phylo
putPhylo :: PhyloId -> GargServer PutPhylo
putPhylo = undefined
-}
-- | Instances
instance FromHttpApiData DisplayMode where parseUrlPiece = readTextData
......
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-}
module Gargantext.System.Logging.Types (
LogLevel(..)
......
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