Commit 2acabe07 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Basic implementation of isNodeReadOnly

parent 88fe3802
......@@ -258,6 +258,7 @@ library
Gargantext.Database.Query.Table.NgramsPostag
Gargantext.Database.Query.Table.Node
Gargantext.Database.Query.Table.Node.Error
Gargantext.Database.Query.Table.NodeNode
Gargantext.Database.Query.Table.Node.UpdateOpaleye
Gargantext.Database.Query.Table.User
Gargantext.Database.Query.Tree.Root
......@@ -448,7 +449,6 @@ library
Gargantext.Database.Query.Table.NodeContext
Gargantext.Database.Query.Table.NodeContext_NodeContext
Gargantext.Database.Query.Table.NodeNgrams
Gargantext.Database.Query.Table.NodeNode
Gargantext.Database.Query.Tree
Gargantext.Database.Query.Tree.Error
Gargantext.Database.Schema.Context
......
......@@ -14,6 +14,8 @@ commentary with @some markup@.
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.Database.Query.Table.NodeNode
( module Gargantext.Database.Schema.NodeNode
......@@ -50,6 +52,8 @@ import Gargantext.Database.Schema.NodeNode
import Gargantext.Prelude
import Opaleye
import Opaleye qualified as O
import qualified Data.List as L
import qualified Prelude
queryNodeNodeTable :: Select NodeNodeRead
queryNodeNodeTable = selectTable nodeNodeTable
......@@ -239,9 +243,43 @@ selectPublicNodes :: HasDBid NodeType => (Hyperdata a, DefaultFromField SqlJsonb
selectPublicNodes = runOpaQuery (queryWithType NodeFolderPublic)
-- | A 'Node' is read-only if there exist a match in the node_nodes directory
-- where the source is a public folder.
isNodeReadOnly :: NodeId -> DBCmd err Bool
isNodeReadOnly _ = panicTrace "todo isNodeReadOnly"
-- where the source is a public folder. Certain category of nodes (like private/shared folders, etc)
-- are automatically read-only.
isNodeReadOnly :: HasDBid NodeType => NodeId -> DBCmd err Bool
isNodeReadOnly nodeId = do
( result :: [NodeId] ) <- runOpaQuery $ do
node <- queryNodeTable
nn <- queryNodeNodeTable
where_ $ node ^. node_typename .== sqlInt4 (toDBid NodeFolderPublic)
let isLinked = (nn ^. nn_node1_id .== pgNodeId nodeId) .|| (nn ^. nn_node2_id .== pgNodeId nodeId)
where_ isLinked
pure $ nn ^. nn_node1_id
return $ Prelude.not (L.null result) -- Return True if any rows are found
where
-- FIXME(and) whitelisting.
_typesWhiteList :: [ NodeType ]
_typesWhiteList = [
NodeFolder
, NodeCorpus
, NodeCorpusV3
, NodeTexts
, NodeDocument
, NodeAnnuaire
, NodeContact
, NodeGraph
, NodePhylo
, NodeDashboard
, NodeList
, NodeModel
, NodeListCooc
, Notes
, Calc
, NodeFrameVisio
, NodeFrameNotebook
, NodeFile
]
queryWithType :: HasDBid NodeType
=> NodeType
......
......@@ -13,6 +13,7 @@ module Test.API.UpdateList (
-- * Useful helpers
, updateNode
, newPrivateFolderForUser
) where
import Control.Lens (mapped, over)
......
......@@ -71,6 +71,7 @@ tests = sequential $ aroundAll withTestDB $ describe "Database" $ do
it "Can perform search with spaces for doc in db" corpusSearchDB01
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
nodeStoryTests :: Spec
nodeStoryTests = sequential $
......
......@@ -16,11 +16,15 @@ 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
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.Database.Types
import Test.Tasty.HUnit
......@@ -30,3 +34,18 @@ testGetUserRootPublicNode testEnv = do
alicePublicFolder <- flip runReaderT testEnv $ runTestMonad $ do
getUserRootPublicNode aliceId
_node_typename alicePublicFolder @?= (toDBid NodeFolderPublic)
testIsReadOnlyWorks :: TestEnv -> Assertion
testIsReadOnlyWorks testEnv = do
alicePrivateFolderId <- newPrivateFolderForUser testEnv "alice"
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
isRO @?= False
-- TODO(adn): Move the node under the public node, then
-- we check that's public.
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