Commit 121f8a4b authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Refactors NodeNodeCategory

This commit refactors the `NodeNodeCategory` so that we create a better
hierarchy to account for node publication, including all the policies it
might have.
parent 35fd225e
...@@ -12,19 +12,19 @@ Portability : POSIX ...@@ -12,19 +12,19 @@ Portability : POSIX
module Gargantext.Database.Query.Table.Node.Update (Update(..), update) module Gargantext.Database.Query.Table.Node.Update (Update(..), update)
where where
import Data.Text qualified as DT
import Database.PostgreSQL.Simple ( Only(Only) ) import Database.PostgreSQL.Simple ( Only(Only) )
import Data.Text qualified as DT
import Gargantext.Core (fromDBid)
import Gargantext.Core.Notifications.CentralExchange.Types qualified as CE import Gargantext.Core.Notifications.CentralExchange.Types qualified as CE
import Gargantext.Core.Types (Name) import Gargantext.Core.Types (Name)
import Gargantext.Database.Admin.Config () import Gargantext.Database.Admin.Config ()
import Gargantext.Database.Query.Table.Node (getParentId, getNode, getUserRootPublicNode) import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude (Cmd, DBCmd, runPGSQuery) import Gargantext.Database.Prelude (Cmd, DBCmd, runPGSQuery)
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Table.Node (getParentId, getNode, getUserRootPublicNode)
import Gargantext.Database.Query.Table.NodeNode (NodePublishPolicy(..), isNodeReadOnly, SourceId (..), TargetId(..), publishNode, unpublishNode)
import Gargantext.Database.Schema.Node import Gargantext.Database.Schema.Node
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core (fromDBid)
import Gargantext.Database.Query.Table.NodeNode (isNodeReadOnly, SourceId (..), TargetId(..), publishNode, unpublishNode)
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Admin.Types.Node
-- import Data.ByteString -- import Data.ByteString
--rename :: NodeId -> Text -> IO ByteString --rename :: NodeId -> Text -> IO ByteString
...@@ -78,7 +78,10 @@ update loggedInUserId u@(Move sourceId targetId) = do ...@@ -78,7 +78,10 @@ update loggedInUserId u@(Move sourceId targetId) = do
do case fromDBid $ _node_typename targetNode of do case fromDBid $ _node_typename targetNode of
NodeFolderPublic NodeFolderPublic
-> do -> do
publishNode (SourceId sourceId) (TargetId targetId) -- See issue #400, by default we publish in a \"strict\"
-- way by disallowing further edits on the original node,
-- including edits from the owner itself!
publishNode NPP_publish_no_edits_allowed (SourceId sourceId) (TargetId targetId)
pure [ _NodeId $ sourceId] pure [ _NodeId $ sourceId]
_ -> nodeError (NodeIsReadOnly targetId "Target is read only, but not a public folder.") _ -> nodeError (NodeIsReadOnly targetId "Target is read only, but not a public folder.")
(True, False) (True, False)
......
...@@ -266,7 +266,10 @@ publishedNodeIds = map (\(owner, nn) -> (SourceId $ _nn_node2_id nn, TargetId $ ...@@ -266,7 +266,10 @@ publishedNodeIds = map (\(owner, nn) -> (SourceId $ _nn_node2_id nn, TargetId $
do_query = runOpaQuery $ do do_query = runOpaQuery $ do
n <- queryNodeTable n <- queryNodeTable
nn <- queryNodeNodeTable nn <- queryNodeNodeTable
where_ $ (nn ^. nn_category .== sqlInt4 (toDBid NNC_read_only_publish)) let isRO = ors [ (nn ^. nn_category .== sqlInt4 (toDBid $ NNC_publish ro))
| ro <- [minBound .. maxBound]
]
where_ isRO
where_ $ (n ^. node_id .== nn ^. nn_node1_id) where_ $ (n ^. node_id .== nn ^. nn_node1_id)
pure (n ^. node_parent_id, nn) pure (n ^. node_parent_id, nn)
...@@ -309,7 +312,7 @@ isNodeReadOnly targetNodeId = do ...@@ -309,7 +312,7 @@ isNodeReadOnly targetNodeId = do
FROM ParentNodes pn FROM ParentNodes pn
JOIN nodes_nodes nn ON pn.id = nn.node1_id OR pn.id = nn.node2_id JOIN nodes_nodes nn ON pn.id = nn.node1_id OR pn.id = nn.node2_id
JOIN nodes n ON (nn.node1_id = n.id OR nn.node2_id = n.id) JOIN nodes n ON (nn.node1_id = n.id OR nn.node2_id = n.id)
WHERE n.typename = ? AND nn.category = ? WHERE n.typename = ? AND nn.category <= ?
) OR EXISTS ( ) OR EXISTS (
SELECT 1 SELECT 1
FROM nodes FROM nodes
...@@ -318,7 +321,7 @@ isNodeReadOnly targetNodeId = do ...@@ -318,7 +321,7 @@ isNodeReadOnly targetNodeId = do
|] ( targetNodeId |] ( targetNodeId
, toDBid NodeFolderPublic , toDBid NodeFolderPublic
, toDBid NNC_read_only_publish , toDBid (maxBound @NodePublishPolicy)
, targetNodeId , targetNodeId
, toDBid NodeFolderPublic , toDBid NodeFolderPublic
) )
...@@ -357,9 +360,9 @@ shareNode (SourceId sourceId) (TargetId targetId) = ...@@ -357,9 +360,9 @@ shareNode (SourceId sourceId) (TargetId targetId) =
-- node_node table backwards, i.e. the public folder first as -- node_node table backwards, i.e. the public folder first as
-- the 'node1_id', and the shared node as the target, so we -- the 'node1_id', and the shared node as the target, so we
-- honour this. -- honour this.
publishNode :: SourceId -> TargetId -> DBCmd err () publishNode :: NodePublishPolicy -> SourceId -> TargetId -> DBCmd err ()
publishNode (SourceId sourceId) (TargetId targetId) = publishNode publishPolicy (SourceId sourceId) (TargetId targetId) =
void $ insertNodeNode [ NodeNode targetId sourceId Nothing (Just NNC_read_only_publish) ] void $ insertNodeNode [ NodeNode targetId sourceId Nothing (Just $ NNC_publish publishPolicy) ]
-- /NOTE/: Even though the semantic of the relationships it -- /NOTE/: Even though the semantic of the relationships it
-- source -> target, by historical reason we store this in the -- source -> target, by historical reason we store this in the
......
...@@ -26,6 +26,7 @@ module Gargantext.Database.Schema.NodeNode ( ...@@ -26,6 +26,7 @@ module Gargantext.Database.Schema.NodeNode (
-- * Types -- * Types
, NodeNodePoly(..) , NodeNodePoly(..)
, NodeNodeCategory(..) , NodeNodeCategory(..)
, NodePublishPolicy(..)
-- * Lenses -- * Lenses
, nn_node1_id , nn_node1_id
...@@ -60,15 +61,32 @@ type NodeNodeRead = NodeNodePoly (Field SqlInt4) ...@@ -60,15 +61,32 @@ type NodeNodeRead = NodeNodePoly (Field SqlInt4)
(Field SqlInt4) (Field SqlInt4)
data NodeNodeCategory data NodeNodeCategory
= -- | Read-only publishing relationship between nodes. = -- | Read-only/publishing relationship between nodes.
NNC_read_only_publish NNC_publish !NodePublishPolicy
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
data NodePublishPolicy
= -- | No edits are allowed (not even the ones from the owner)
NPP_publish_no_edits_allowed
-- | Edits after publishing are allowed only from the owner or the super user
| NPP_publish_edits_only_owner_or_super
deriving (Show, Eq, Ord, Enum, Bounded)
instance HasDBid NodeNodeCategory where instance HasDBid NodeNodeCategory where
toDBid = \case toDBid = \case
NNC_read_only_publish -> 0 NNC_publish roCats -> toDBid roCats
lookupDBid x = case x of lookupDBid x =
0 -> Just NNC_read_only_publish NNC_publish <$> lookupDBid x
instance HasDBid NodePublishPolicy where
toDBid = \case
NPP_publish_no_edits_allowed
-> 0
NPP_publish_edits_only_owner_or_super
-> 1
lookupDBid = \case
0 -> Just NPP_publish_no_edits_allowed
1 -> Just NPP_publish_edits_only_owner_or_super
_ -> Nothing _ -> Nothing
instance DefaultFromField SqlInt4 (Maybe NodeNodeCategory) where instance DefaultFromField SqlInt4 (Maybe NodeNodeCategory) where
......
...@@ -20,6 +20,7 @@ import Gargantext.Core ...@@ -20,6 +20,7 @@ import Gargantext.Core
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Database.Action.User (getUserId) import Gargantext.Database.Action.User (getUserId)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude (DBCmd)
import Gargantext.Database.Query.Table.Node import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Table.NodeNode import Gargantext.Database.Query.Table.NodeNode
import Gargantext.Database.Schema.Node (NodePoly(..)) import Gargantext.Database.Schema.Node (NodePoly(..))
...@@ -28,6 +29,9 @@ import Test.API.Setup (createAliceAndBob) ...@@ -28,6 +29,9 @@ import Test.API.Setup (createAliceAndBob)
import Test.Database.Types import Test.Database.Types
import Test.Tasty.HUnit import Test.Tasty.HUnit
publishStrict :: SourceId -> TargetId -> DBCmd err ()
publishStrict = publishNode NPP_publish_no_edits_allowed
testGetUserRootPublicNode :: TestEnv -> Assertion testGetUserRootPublicNode :: TestEnv -> Assertion
testGetUserRootPublicNode testEnv = do testGetUserRootPublicNode testEnv = do
[aliceId, _bobId] <- createAliceAndBob testEnv [aliceId, _bobId] <- createAliceAndBob testEnv
...@@ -47,7 +51,7 @@ testIsReadOnlyWorks testEnv = do ...@@ -47,7 +51,7 @@ testIsReadOnlyWorks testEnv = do
isNodeReadOnly corpusId >>= liftIO . (@?= False) isNodeReadOnly corpusId >>= liftIO . (@?= False)
-- Publish the node, then check that's now public. -- Publish the node, then check that's now public.
publishNode (SourceId corpusId) (TargetId alicePublicFolderId) publishStrict (SourceId corpusId) (TargetId alicePublicFolderId)
isNodeReadOnly corpusId >>= liftIO . (@?= True) isNodeReadOnly corpusId >>= liftIO . (@?= True)
-- Finally check that if we unpublish, the node is back to normal -- Finally check that if we unpublish, the node is back to normal
...@@ -66,7 +70,7 @@ testPublishRecursiveFirstLevel testEnv = do ...@@ -66,7 +70,7 @@ testPublishRecursiveFirstLevel testEnv = do
aliceFolderId <- insertDefaultNode NodeFolder alicePrivateFolderId aliceUserId aliceFolderId <- insertDefaultNode NodeFolder alicePrivateFolderId aliceUserId
corpusId <- insertDefaultNode NodeCorpus aliceFolderId aliceUserId corpusId <- insertDefaultNode NodeCorpus aliceFolderId aliceUserId
publishNode (SourceId aliceFolderId) (TargetId alicePublicFolderId) publishStrict (SourceId aliceFolderId) (TargetId alicePublicFolderId)
isNodeReadOnly aliceFolderId >>= liftIO . (@?= True) isNodeReadOnly aliceFolderId >>= liftIO . (@?= True)
isNodeReadOnly corpusId >>= liftIO . (@?= True) isNodeReadOnly corpusId >>= liftIO . (@?= True)
...@@ -84,7 +88,7 @@ testPublishRecursiveNLevel testEnv = do ...@@ -84,7 +88,7 @@ testPublishRecursiveNLevel testEnv = do
aliceSubFolderId <- insertDefaultNode NodeFolder aliceFolderId aliceUserId aliceSubFolderId <- insertDefaultNode NodeFolder aliceFolderId aliceUserId
corpusId <- insertDefaultNode NodeCorpus aliceSubFolderId aliceUserId corpusId <- insertDefaultNode NodeCorpus aliceSubFolderId aliceUserId
publishNode (SourceId aliceFolderId) (TargetId alicePublicFolderId) publishStrict (SourceId aliceFolderId) (TargetId alicePublicFolderId)
isNodeReadOnly aliceFolderId >>= liftIO . (@?= True) isNodeReadOnly aliceFolderId >>= liftIO . (@?= True)
isNodeReadOnly aliceSubFolderId >>= liftIO . (@?= True) isNodeReadOnly aliceSubFolderId >>= liftIO . (@?= True)
......
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