Commit 0336eec7 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Improve test for publishing a node

parent b3a00112
......@@ -32,7 +32,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
manager <- newManager defaultManagerSettings
let clientEnv prt = mkClientEnv manager (baseUrl { baseUrlPort = prt })
createAliceAndBob testEnv
void $ createAliceAndBob testEnv
let gargAdminClient = (genericClient :: GargAdminAPI (AsClientT ClientM))
roots = (getRootsEp . rootsEp $ gargAdminClient :: ClientM [Node HyperdataUser])
......
......@@ -7,6 +7,7 @@ module Test.API.GraphQL (
tests
) where
import Control.Monad (void)
import Gargantext.Core.Types.Individu
import Prelude
import Servant.Auth.Client ()
......@@ -24,11 +25,11 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
it "setup DB triggers" $ \SpecContext{..} -> setupEnvironment _sctx_env
describe "get_user_infos" $ do
it "allows 'alice' to see her own info" $ \(SpecContext testEnv port app _) -> do
createAliceAndBob testEnv
it "allows 'alice' to see her own info" $ \SpecContext{..} -> do
void $ createAliceAndBob _sctx_env
withApplication app $ do
withValidLogin port "alice" (GargPassword "alice") $ \_clientEnv token -> do
withApplication _sctx_app $ do
withValidLogin _sctx_port "alice" (GargPassword "alice") $ \_clientEnv token -> do
let query = [r| { "query": "{ user_infos(user_id: 2) { ui_id, ui_email } }" } |]
let expected = [json| {"data":{"user_infos":[{"ui_id":2,"ui_email":"alice@gargan.text"}]}} |]
protected token "POST" "/gql" query `shouldRespondWithFragment` expected
......
......@@ -39,7 +39,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" $ \(SpecContext testEnv port _ _) -> do
createAliceAndBob testEnv
void $ createAliceAndBob testEnv
let gargAdminClient = (genericClient :: GargAdminAPI (AsClientT ClientM))
admin_user_api_get = (getRootsEp . rootsEp $ gargAdminClient :: ClientM [Node HyperdataUser])
......
......@@ -28,7 +28,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
it "setup DB triggers" $ \SpecContext{..} -> do
setupEnvironment _sctx_env
-- Let's create the Alice user.
createAliceAndBob _sctx_env
void $ createAliceAndBob _sctx_env
beforeAllWith createSoySauceCorpus $ do
it "should return sauce in the search (#415)" $ \SpecContext{..} -> do
......
......@@ -16,6 +16,7 @@ module Test.API.UpdateList (
, checkEither
, newPrivateFolderForUser
, newPublicFolderForUser
) where
import Control.Lens (mapped, over)
......@@ -49,10 +50,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
......@@ -91,8 +92,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
......
......@@ -72,6 +72,7 @@ tests = sequential $ aroundAll withTestDB $ describe "Database" $ do
describe "Publishing a node" $ do
it "Returns the root public folder for a user" testGetUserRootPublicNode
it "Correctly detects if a node is read only" testIsReadOnlyWorks
it "Publish the root and its first level children" testPublishRecursiveFirstLevel
nodeStoryTests :: Spec
nodeStoryTests = sequential $
......
......@@ -9,6 +9,7 @@ Portability : POSIX
-}
{-# 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,35 @@ testGetUserRootPublicNode testEnv = do
testIsReadOnlyWorks :: TestEnv -> Assertion
testIsReadOnlyWorks testEnv = do
alicePrivateFolderId <- newPrivateFolderForUser testEnv "alice"
isRO <- flip runReaderT testEnv $ runTestMonad $ do
alicePublicFolderId <- newPublicFolderForUser testEnv "alice"
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
isNodeReadOnly corpusId >>= liftIO . (@?= False)
isRO @?= False
-- Publish the node, then check that's now public.
publishNode (SourceId corpusId) (TargetId alicePublicFolderId)
isNodeReadOnly corpusId >>= liftIO . (@?= True)
-- TODO(adn): Move the node under the public node, then
-- we check that's public.
-- Finally check that if we unpublish, the node is back to normal
unpublishNode (SourceId corpusId) (TargetId alicePublicFolderId)
isNodeReadOnly corpusId >>= liftIO . (@?= False)
-- | In this test, we check that if we publish the root of a subtree,
-- then all the children (up to the first level) are also marked read-only.
testPublishRecursiveFirstLevel :: TestEnv -> Assertion
testPublishRecursiveFirstLevel testEnv = do
alicePrivateFolderId <- newPrivateFolderForUser testEnv "alice"
alicePublicFolderId <- newPublicFolderForUser testEnv "alice"
flip runReaderT testEnv $ runTestMonad $ do
-- Create a corpus, by default is not read only
aliceUserId <- getUserId (UserName "alice")
aliceFolderId <- insertDefaultNode NodeFolder alicePrivateFolderId aliceUserId
corpusId <- insertDefaultNode NodeCorpus aliceFolderId aliceUserId
publishNode (SourceId aliceFolderId) (TargetId alicePublicFolderId)
isNodeReadOnly aliceFolderId >>= liftIO . (@?= True)
isNodeReadOnly corpusId >>= liftIO . (@?= True)
......@@ -26,8 +26,6 @@ import Gargantext.API.Errors.Types qualified as Errors
import Gargantext.API.Ngrams.Types qualified as Ngrams
import Gargantext.API.Node.Corpus.New (ApiInfo(..))
import Gargantext.API.Node.Types (RenameNode(..), WithQuery(..))
import Gargantext.Core.AsyncUpdates.CentralExchange.Types qualified as CET
import Gargantext.Core.AsyncUpdates.Dispatcher.Types qualified as DET
import Gargantext.Core.NodeStory.Types qualified as NS
import Gargantext.Core.Notifications.CentralExchange.Types qualified as CET
import Gargantext.Core.Notifications.Dispatcher.Types qualified as DET
......
......@@ -7,11 +7,8 @@ import Gargantext.Prelude hiding (isInfixOf)
import Control.Concurrent.Async (asyncThreadId, withAsync)
import Control.Monad
import Data.Text (isInfixOf)
import Gargantext.Core.AsyncUpdates.CentralExchange qualified as CE
import Gargantext.Core.AsyncUpdates.Dispatcher qualified as D
import Gargantext.Core.Notifications.CentralExchange qualified as CE
import Gargantext.Core.Notifications.Dispatcher qualified as D
import Gargantext.Core.Notifications.Dispatcher.Types qualified as DT
import Gargantext.Core.Config.Types (NotificationsConfig(..))
import Shelly hiding (FilePath)
import System.IO
......
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