[test] notification on node move

Also, some small refactorings.
parent 3d5d74ab
Pipeline #7259 passed with stages
in 82 minutes and 13 seconds
......@@ -9,8 +9,6 @@ Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
module Gargantext.API.Node.Share
where
......@@ -57,22 +55,22 @@ api userInviting nId (ShareTeamParams user') = do
pure u
Left _err -> do
username' <- getUsername userInviting
_ <- case username' `List.elem` arbitraryUsername of
True -> do
if username' `List.elem` arbitraryUsername
then do
-- printDebug "[G.A.N.Share.api]" ("Demo users are not allowed to invite" :: Text)
pure ()
False -> do
else do
-- TODO better analysis of the composition of what is shared
children <- findNodesWithType nId [NodeList] [ NodeFolderShared
, NodeTeam
, NodeFolder
, NodeCorpus
]
_ <- case List.null children of
True -> do
_ <- if List.null children
then do
-- printDebug "[G.A.N.Share.api]" ("Invitation is enabled if you share a corpus at least" :: Text)
pure $ UnsafeMkUserId 0
False -> do
else do
-- printDebug "[G.A.N.Share.api]" ("Your invitation is sent to: " <> user'')
newUser user''
pure ()
......
......@@ -60,9 +60,9 @@ update loggedInUserId (Move sourceId targetId) = do
mbParentId <- getParentId sourceId
-- if the source and the target are the same, this is identity.
case sourceId == targetId of
True -> pure [ _NodeId sourceId ]
False -> do
if sourceId == targetId
then pure [ _NodeId sourceId ]
else do
isSourceRO <- isNodeReadOnly sourceId
isTargetRO <- isNodeReadOnly targetId
......@@ -70,24 +70,29 @@ update loggedInUserId (Move sourceId targetId) = do
-- act accordingly.
ids <- case (isSourceRO, isTargetRO) of
(False, False)
-> -- both are not read-only, normal move
move_db_update sourceId targetId
-> do
-- both are not read-only, normal move
move_db_update sourceId targetId
(False, True)
-> do void $ publish_node (SourceId sourceId) (TargetId targetId) NPP_publish_no_edits_allowed
move_db_update sourceId targetId
-> do
void $ publish_node (SourceId sourceId) (TargetId targetId) NPP_publish_no_edits_allowed
move_db_update sourceId targetId
(True, False)
-> -- the source is read only. If we are the owner we allow unpublishing.
-- FIXME(adn) is this check enough?
do sourceNode <- getNode sourceId
case _node_user_id sourceNode == loggedInUserId of
True -> do
userPublicFolderNode <- getUserRootPublicNode loggedInUserId
unpublishNode (SourceId $ sourceId) (TargetId $ _node_id userPublicFolderNode)
move_db_update sourceId targetId
False -> nodeError (NodeIsReadOnly targetId "logged user is not allowed to move/unpublish a read-only node")
-> do
-- the source is read only. If we are the owner we allow unpublishing.
-- FIXME(adn) is this check enough?
sourceNode <- getNode sourceId
if _node_user_id sourceNode == loggedInUserId
then do
userPublicFolderNode <- getUserRootPublicNode loggedInUserId
unpublishNode (SourceId $ sourceId) (TargetId $ _node_id userPublicFolderNode)
move_db_update sourceId targetId
else
nodeError (NodeIsReadOnly targetId "logged user is not allowed to move/unpublish a read-only node")
(True, True)
-> -- this case is not allowed.
nodeError (NodeIsReadOnly targetId "Both the source and the target are read-only.")
-> do
-- this case is not allowed.
nodeError (NodeIsReadOnly targetId "Both the source and the target are read-only.")
for_ mbParentId $ CE.ce_notify . CE.UpdateTreeFirstLevel
CE.ce_notify $ CE.UpdateTreeFirstLevel targetId
......
......@@ -26,6 +26,9 @@ import Control.Lens ((^.))
import Control.Monad (void)
import Control.Monad.STM (atomically)
import Data.Aeson qualified as Aeson
import Data.ByteString qualified as BS
import Data.Text qualified as T
import Data.Text.Encoding qualified as TE
import Fmt ((+|), (|+))
import Gargantext.API.Admin.Auth.Types (AuthResponse, authRes_token, authRes_tree_id)
import Gargantext.Core.Config (gc_notifications_config)
......@@ -172,6 +175,16 @@ tests = sequential $ around withTestDBAndPort $ do
let query = [r| {"name": "newName"} |]
protected token "PUT" (mkUrl port $ "/node/" +| cId |+ "/rename") query
it "WS notification on node move works" $ \ctx@(SpecContext testEnv port app _) -> do
checkNotification ctx $ \authRes -> do
let token = authRes ^. authRes_token
cId <- newCorpusForUser testEnv "alice"
cId2 <- newCorpusForUser testEnv "alice"
void $ withApplication app $ do
let query = BS.fromStrict $ TE.encodeUtf8 $ "[" <> (T.pack $ show cId2) <> "]"
protected token "PUT" (mkUrl port $ "/node/" +| cId |+ "/move/" +| cId2 |+ "" ) query
-- | Given spec context and an action, call that action to perform
......
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