Verified Commit 28581725 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into dev-flake-merge-0.0.7.1

parents d65762f6 ca1aa195
## Version 0.0.7.1 [RELEASE CANDIDATE 007]
## Version 0.0.7.1.1
* [FRONT][FEAT][[Tree search] Add possibility to share a node URL (without the username), that will redirect to the right instance and node (#548)](https://gitlab.iscpif.fr/gargantext/purescript-gargantext/issues/548)
## Version 0.0.7.1
* [FRONT][FIX][Fix breadcrumbs (#648)](https://gitlab.iscpif.fr/gargantext/purescript-gargantext/issues/648)
......
......@@ -5,7 +5,7 @@ cabal-version: 3.4
-- see: https://github.com/sol/hpack
name: gargantext
version: 0.0.7.1
version: 0.0.7.1.1
synopsis: Search, map, share
description: Please see README.md
category: Data
......@@ -133,6 +133,7 @@ library
Gargantext.API.Node.Corpus.Update
Gargantext.API.Node.File
Gargantext.API.Node.Share
Gargantext.API.Node.ShareURL
Gargantext.API.Node.Update
Gargantext.API.Prelude
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, unNodeId)
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 (unNodeId i)
......@@ -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.Document.Export 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.Public qualified as Public
import Gargantext.Core.Types.Individu (User(..))
......@@ -222,6 +223,7 @@ type GargPrivateAPI' =
:<|> List.GETAPI
:<|> List.JSONAPI
:<|> List.CSVAPI
:<|> "shareurl" :> ShareURL.API
{-
:<|> "wait" :> Summary "Wait test"
:> Capture "x" Int
......@@ -305,6 +307,7 @@ serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser userNodeId userId)
:<|> List.getApi
:<|> List.jsonApi
:<|> List.csvApi
:<|> ShareURL.api
-- :<|> 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