Commit 59d96471 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

get_user_root_node_folder picks the oldest public folder

Previous to this commit, `get_user_root_node_folder` would fail with
a `UserHasTooManyRoots` in case this was called on a tree which had
more than one "public" folder.

We fix this by taking the oldest available node, which will always
correspond to the notion of "root", being the first ever created.
parent 29c26d19
Pipeline #6969 passed with stages
in 50 minutes and 50 seconds
......@@ -81,6 +81,7 @@ import Gargantext.Database.Schema.Node
import Gargantext.Prelude hiding (sum, head)
import Opaleye hiding (FromField)
import Prelude hiding (null, id, map, sum)
import qualified Data.List.NonEmpty as NE
queryNodeSearchTable :: Select NodeSearchRead
......@@ -448,10 +449,14 @@ get_user_root_node_folder nty userId = do
where_ $ (n ^. node_typename .== sqlInt4 (toDBid nty)) .&&
(n ^. node_user_id .== sqlInt4 (_UserId userId))
pure n
case result of
[] -> nodeError $ NodeLookupFailed $ UserFolderDoesNotExist userId
[n] -> pure n
folders -> nodeError $ NodeLookupFailed $ UserHasTooManyRoots userId (map _node_id folders)
case NE.nonEmpty result of
Nothing
-> nodeError $ NodeLookupFailed $ UserFolderDoesNotExist userId
-- See https://gitlab.iscpif.fr/gargantext/haskell-gargantext/merge_requests/350#note_12732
-- User might have more than one public folder, in which case we need to take the one with the
-- smallest id.
Just folders
-> pure $ NE.head (NE.sortWith _node_id folders)
-- | An input 'NodeId' identifies a user node if its typename is 'NodeUser' and it has no parent_id.
isUserNode :: HasDBid NodeType => NodeId -> DBCmd err Bool
......
......@@ -16,7 +16,6 @@ module Test.Database.Operations.PublishNode where
import Prelude
import Control.Monad.Reader
import Gargantext.Core
import Gargantext.Core.Types.Individu
import Gargantext.Database.Action.User (getUserId)
import Gargantext.Database.Admin.Types.Node
......@@ -35,12 +34,15 @@ publishStrict = publishNode NPP_publish_no_edits_allowed
publishLenient :: SourceId -> TargetId -> DBCmd err ()
publishLenient = publishNode NPP_publish_edits_only_owner_or_super
-- Also test that in the presence of /multiple/ public folders, we take the
-- first one (i.e. the \"root\" one).
testGetUserRootPublicNode :: TestEnv -> Assertion
testGetUserRootPublicNode testEnv = do
[aliceId, _bobId] <- createAliceAndBob testEnv
alicePublicFolder <- flip runReaderT testEnv $ runTestMonad $ do
getUserRootPublicNode aliceId
_node_typename alicePublicFolder @?= (toDBid NodeFolderPublic)
publicFolder2 <- newPublicFolderForUser testEnv "alice"
flip runReaderT testEnv $ runTestMonad $ do
rootPublicFolder <- getUserRootPublicNode aliceId
liftIO $ assertBool "wrong public node detected" $ (_node_id rootPublicFolder) /= publicFolder2
testIsReadOnlyWorks :: TestEnv -> Assertion
testIsReadOnlyWorks testEnv = do
......
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