Commit c32ea704 authored by Karen Konou's avatar Karen Konou

API: URL Share route

parent 030f7dad
Pipeline #5534 passed with stages
in 135 minutes and 58 seconds
...@@ -74,6 +74,7 @@ library ...@@ -74,6 +74,7 @@ library
Gargantext.API.Node.Corpus.Update Gargantext.API.Node.Corpus.Update
Gargantext.API.Node.File Gargantext.API.Node.File
Gargantext.API.Node.Share Gargantext.API.Node.Share
Gargantext.API.Node.ShareURL
Gargantext.API.Node.Update Gargantext.API.Node.Update
Gargantext.API.Prelude Gargantext.API.Prelude
Gargantext.API.Routes Gargantext.API.Routes
......
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.API.Node.ShareURL where
import Data.Text
import Gargantext.Prelude
import Gargantext.API.Prelude
import Servant
import Gargantext.Core.Types (NodeType, NodeId)
import Gargantext.Database.Prelude (HasConfig (hasConfig), CmdCommon)
import Control.Lens.Getter (view)
import Gargantext.Prelude.Config (gc_url)
import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors (BackendInternalError)
type API = Summary "Fetch URL for sharing a node"
:> QueryParam "type" NodeType
:> QueryParam "id" NodeId
:> Get '[JSON] Text
api :: ServerT API (GargM Env BackendInternalError)
api = getUrl
getUrl :: (CmdCommon env) =>
Maybe NodeType -> Maybe NodeId -> GargM env BackendInternalError Text
getUrl nt id = do
-- TODO add check that the node is able to be shared (in a shared folder)
case nt of
Nothing -> pure "Invalid node Type"
Just t ->
case id of
Nothing -> pure "Invalid node ID"
Just i -> do
url <- view $ hasConfig . gc_url
pure $ url <> "/#/share/" <> show t <> "/" <> show i
...@@ -43,6 +43,7 @@ import Gargantext.API.Node.Corpus.Export.Types qualified as CorpusExport ...@@ -43,6 +43,7 @@ import Gargantext.API.Node.Corpus.Export.Types qualified as CorpusExport
import Gargantext.API.Node.Corpus.New qualified as New import Gargantext.API.Node.Corpus.New qualified as New
import Gargantext.API.Node.Document.Export qualified as DocumentExport import Gargantext.API.Node.Document.Export qualified as DocumentExport
import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport
import Gargantext.API.Node.ShareURL qualified as ShareURL
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Public qualified as Public import Gargantext.API.Public qualified as Public
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
...@@ -222,6 +223,7 @@ type GargPrivateAPI' = ...@@ -222,6 +223,7 @@ type GargPrivateAPI' =
:<|> List.GETAPI :<|> List.GETAPI
:<|> List.JSONAPI :<|> List.JSONAPI
:<|> List.CSVAPI :<|> List.CSVAPI
:<|> "shareurl" :> ShareURL.API
{- {-
:<|> "wait" :> Summary "Wait test" :<|> "wait" :> Summary "Wait test"
:> Capture "x" Int :> Capture "x" Int
...@@ -305,6 +307,7 @@ serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser userNodeId userId) ...@@ -305,6 +307,7 @@ serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser userNodeId userId)
:<|> List.getApi :<|> List.getApi
:<|> List.jsonApi :<|> List.jsonApi
:<|> List.csvApi :<|> List.csvApi
:<|> ShareURL.api
-- :<|> waitAPI -- :<|> waitAPI
......
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