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