Commit 92b6a44c authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

fix(policy): Relax a bit ownership checks for moveChecks for shared nodes

This commit fixes a bug where a user member of a team (but NOT the owner
of such team) couldn't move nodes.
parent bc1f1f17
Pipeline #7467 passed with stages
in 38 minutes and 23 seconds
......@@ -266,10 +266,11 @@ nodeWriteChecks nid =
-- if:
-- * He/she is a super user
-- * He/she owns the target or the source
-- * The node has been shared with the user
moveChecks :: SourceId -> TargetId -> BoolExpr AccessCheck
moveChecks (SourceId sourceId) (TargetId targetId) =
BAnd (nodeUser sourceId `BOr` nodeSuper sourceId)
(nodeUser targetId `BOr` nodeUser targetId)
BAnd (nodeUser sourceId `BOr` nodeSuper sourceId `BOr` nodeShared sourceId)
(nodeUser targetId `BOr` nodeUser targetId `BOr` nodeShared targetId)
publishChecks :: NodeId -> BoolExpr AccessCheck
publishChecks nodeId =
......
......@@ -9,6 +9,7 @@ module Test.API.Private.Move (
import Gargantext.API.Errors
import Gargantext.Core.Types
import Gargantext.Core.Types.Individu
import Gargantext.API.Node.Share.Types
import Gargantext.Database.Query.Table.NodeNode (SourceId(..), TargetId(..))
import Gargantext.Prelude
import Servant.Client.Streaming
......@@ -55,6 +56,26 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
-- Test that moving child1 into child2 works.
res <- checkEither $ runClientM (move_node token (SourceId child2) (TargetId child1)) clientEnv
res `shouldBe` [child2]
it "should allow moving one folder into another (as team member)" $ \(SpecContext testEnv serverPort app _) -> do
withApplication app $ do
(teamNode, child1, child2) <- liftIO $ do
-- Let's create (once) the shared team folder
void $ newShareFolderForUser testEnv alice
teamNode <- newTeamWithOwner testEnv alice "Alice's Team"
child1 <- addFolderForUser testEnv alice "child1" teamNode
child2 <- addFolderForUser testEnv alice "child2" teamNode
pure (teamNode, child1, child2)
-- let's make bob a team member.
withValidLogin serverPort "alice" (GargPassword "alice") $ \clientEnv token -> liftIO $ do
let params = ShareTeamParams "bob"
res <- checkEither $ runClientM (addTeamMember token teamNode params) clientEnv
res `shouldBe` UnsafeMkNodeId 1
withValidLogin serverPort "bob" (GargPassword "bob") $ \clientEnv token -> liftIO $ do
-- Test that moving child1 into child2 works.
res <- checkEither $ runClientM (move_node token (SourceId child2) (TargetId child1)) clientEnv
res `shouldBe` [child2]
describe "Publishing a Corpus" $ do
......
......@@ -28,6 +28,7 @@ module Test.API.Routes (
, delete_node
, add_form_to_list
, add_tsv_to_list
, addTeamMember
) where
import Data.Text.Encoding qualified as TE
......@@ -37,6 +38,7 @@ import Gargantext.API.Errors
import Gargantext.API.HashedResponse (HashedResponse)
import Gargantext.API.Ngrams.List.Types (WithJsonFile, WithTextFile)
import Gargantext.API.Ngrams.Types ( NgramsTable, NgramsTablePatch, OrderBy, TabType, Versioned, VersionedWithCount )
import Gargantext.API.Node.Share.Types (ShareNodeParams(..))
import Gargantext.API.Routes.Client
import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.List (updateListJSONEp, updateListTSVEp)
......@@ -44,6 +46,7 @@ import Gargantext.API.Routes.Named.Node hiding (treeAPI)
import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI)
import Gargantext.API.Routes.Named.Publish (PublishAPI(..))
import Gargantext.API.Routes.Named.Publish (PublishRequest(..))
import Gargantext.API.Routes.Named.Share (shareNodeEp)
import Gargantext.API.Routes.Named.Table
import Gargantext.API.Routes.Named.Tree (nodeTreeEp)
import Gargantext.API.Types () -- MimeUnrender instances
......@@ -337,3 +340,21 @@ publish_node (toServantToken -> token) sourceId policy = fmap UnsafeMkNodeId $
& publishAPI
& publishEp
& ($ PublishRequest policy)
addTeamMember :: Token -> NodeId -> ShareNodeParams -> ClientM NodeId
addTeamMember (toServantToken -> token) nodeId params = fmap UnsafeMkNodeId $
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
& backendAPI'
& mkBackEndAPI
& gargAPIVersion
& gargPrivateAPI
& mkPrivateAPI
& ($ token)
& nodeEp
& nodeEndpointAPI
& ($ nodeId)
& shareAPI
& shareNodeEp
& ($ params)
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