Commit 4bd20e5d authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Improve test for publishing a node

parent 0de4602f
Pipeline #6766 passed with stages
in 25 minutes and 22 seconds
......@@ -40,7 +40,7 @@ privateTests =
-- FIXME(adn): unclear if this is useful at all. Doesn't do permission checking.
it "doesn't allow someone with an invalid token to show the results" $ \((testEnv, port), _) -> do
createAliceAndBob testEnv
void $ createAliceAndBob testEnv
let gargAdminClient = (genericClient :: GargAdminAPI (AsClientT ClientM))
admin_user_api_get = (getRootsEp . rootsEp $ gargAdminClient :: ClientM [Node HyperdataUser])
......
......@@ -14,6 +14,7 @@ module Test.API.UpdateList (
-- * Useful helpers
, updateNode
, newPrivateFolderForUser
, newPublicFolderForUser
) where
import Control.Lens (mapped, over)
......@@ -47,10 +48,10 @@ import Gargantext.Core.Text.Ngrams
import Gargantext.Core.Types ( CorpusId, ListId, NodeId, _NodeId)
import Gargantext.Core.Types.Individu
import Gargantext.Core.Types.Main (ListType(..))
import Gargantext.Core.Types (NodeType(..))
import Gargantext.Core.Types (TableResult(..))
import Gargantext.Database.Action.User
import Gargantext.Database.Admin.Types.Hyperdata.Corpus
import Gargantext.Database.Admin.Types.Hyperdata.Folder (defaultHyperdataFolderPrivate)
import Gargantext.Database.Query.Facet qualified as Facet
import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Tree.Root
......@@ -88,8 +89,14 @@ newPrivateFolderForUser env uname = flip runReaderT env $ runTestMonad $ do
uid <- getUserId (UserName uname)
parentId <- getRootId (UserName uname)
let nodeName = "NodeFolderPrivate"
(nodeId:_) <- mk (Just nodeName) (Just defaultHyperdataFolderPrivate) parentId uid
pure nodeId
insertNode NodeFolderPrivate (Just nodeName) Nothing parentId uid
newPublicFolderForUser :: TestEnv -> T.Text -> IO NodeId
newPublicFolderForUser env uname = flip runReaderT env $ runTestMonad $ do
uid <- getUserId (UserName uname)
parentId <- getRootId (UserName uname)
let nodeName = "NodeFolderPublic"
insertNode NodeFolderPublic (Just nodeName) Nothing parentId uid
uploadJSONList :: Wai.Port
-> Token
......
......@@ -8,7 +8,8 @@ Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TupleSections #-}
module Test.Database.Operations.PublishNode where
......@@ -20,13 +21,13 @@ import Gargantext.Core.Types.Individu
import Gargantext.Database.Action.User (getUserId)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Table.NodeNode (isNodeReadOnly)
import Gargantext.Database.Schema.Node (NodePoly(..))
import Test.API.Setup (createAliceAndBob)
import Test.API.UpdateList (newPrivateFolderForUser)
import Test.API.UpdateList (newPrivateFolderForUser, newPublicFolderForUser)
import Test.Database.Types
import Test.Tasty.HUnit
import Gargantext.Database.Query.Table.NodeNode
testGetUserRootPublicNode :: TestEnv -> Assertion
testGetUserRootPublicNode testEnv = do
......@@ -38,14 +39,24 @@ testGetUserRootPublicNode testEnv = do
testIsReadOnlyWorks :: TestEnv -> Assertion
testIsReadOnlyWorks testEnv = do
alicePrivateFolderId <- newPrivateFolderForUser testEnv "alice"
isRO <- flip runReaderT testEnv $ runTestMonad $ do
alicePublicFolderId <- newPublicFolderForUser testEnv "alice"
(corpusId, isRO) <- flip runReaderT testEnv $ runTestMonad $ do
-- Create a corpus, by default is not read only
aliceUserId <- getUserId (UserName "alice")
corpusId <- insertDefaultNode NodeCorpus alicePrivateFolderId aliceUserId
isNodeReadOnly corpusId
(corpusId,) <$> isNodeReadOnly corpusId
isRO @?= False
-- TODO(adn): Move the node under the public node, then
-- we check that's public.
-- Publish the node, then check that's now public.
isRO' <- flip runReaderT testEnv $ runTestMonad $ do
publishNode (SourceId corpusId) (TargetId alicePublicFolderId)
isNodeReadOnly corpusId
isRO' @?= True
-- Finally check that if we unpublish, the node is back to normal
isRO'' <- flip runReaderT testEnv $ runTestMonad $ do
unpublishNode (SourceId corpusId) (TargetId alicePublicFolderId)
isNodeReadOnly corpusId
isRO'' @?= False
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