Commit 3d0edc1b authored by Alexandre Delanoë's avatar Alexandre Delanoë

[SECURITY|COLLAB] can share Node Team only

parent b456323e
...@@ -17,11 +17,13 @@ TODO: configure nodes table in Haskell (Config typenames etc.) ...@@ -17,11 +17,13 @@ TODO: configure nodes table in Haskell (Config typenames etc.)
module Gargantext.Database.Admin.Config module Gargantext.Database.Admin.Config
where where
import Control.Lens (view)
import Data.List (lookup) import Data.List (lookup)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Text (Text,pack) import Data.Text (Text,pack)
import Data.Tuple.Extra (swap) import Data.Tuple.Extra (swap)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Schema.Node
import Gargantext.Prelude import Gargantext.Prelude
-- TODO put this in config.ini file -- TODO put this in config.ini file
...@@ -80,6 +82,9 @@ nodeTypeId n = ...@@ -80,6 +82,9 @@ nodeTypeId n =
-- NodeFavorites -> 15 -- NodeFavorites -> 15
hasNodeType :: forall a. Node a -> NodeType -> Bool
hasNodeType n nt = (view node_typename n) == (nodeTypeId nt)
-- --
-- | Nodes are typed in the database according to a specific ID -- | Nodes are typed in the database according to a specific ID
-- --
......
...@@ -41,12 +41,14 @@ import Database.PostgreSQL.Simple.SqlQQ ...@@ -41,12 +41,14 @@ import Database.PostgreSQL.Simple.SqlQQ
import Gargantext.Core.Types.Main (NodeTree(..), Tree(..)) import Gargantext.Core.Types.Main (NodeTree(..), Tree(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Admin.Types.Node -- (pgNodeId, NodeType(..)) import Gargantext.Database.Admin.Types.Node -- (pgNodeId, NodeType(..))
import Gargantext.Database.Admin.Config (fromNodeTypeId, nodeTypeId) import Gargantext.Database.Admin.Config (fromNodeTypeId, nodeTypeId, hasNodeType)
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType, DocId, allNodeTypes) import Gargantext.Database.Admin.Types.Node (NodeId, NodeType, DocId, allNodeTypes)
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Prelude (Cmd, runPGSQuery) import Gargantext.Database.Prelude (Cmd, runPGSQuery)
import Gargantext.Database.Query.Tree.Error import Gargantext.Database.Query.Tree.Error
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Tree.Root (getRoot) import Gargantext.Database.Query.Tree.Root (getRoot)
import Gargantext.Database.Query.Table.NodeNode (insertNodeNode, getNodeNode) import Gargantext.Database.Query.Table.NodeNode (insertNodeNode, getNodeNode)
import Gargantext.Database.Schema.NodeNode (NodeNodePoly(..)) import Gargantext.Database.Schema.NodeNode (NodeNodePoly(..))
...@@ -79,14 +81,18 @@ sharedTree p n nt = dbTree n nt ...@@ -79,14 +81,18 @@ sharedTree p n nt = dbTree n nt
then set dt_parentId (Just p) n' then set dt_parentId (Just p) n'
else n') else n')
shareNodeWith :: HasNodeError err => NodeId -> User -> Cmd err Int64
shareNodeWith :: NodeId -> User -> Cmd err Int64
shareNodeWith n u = do shareNodeWith n u = do
r <- map _node_id <$> getRoot u nodeToCheck <- getNode n
s <- case head r of if hasNodeType nodeToCheck NodeTeam
Nothing -> panic "no root id" then do
Just r' -> findNodesId r' [NodeFolderShared] r <- map _node_id <$> getRoot u
insertNodeNode $ map (\s' -> NodeNode s' n Nothing Nothing) s s <- case head r of
Nothing -> panic "no root id"
Just r' -> findNodesId r' [NodeFolderShared]
insertNodeNode $ map (\s' -> NodeNode s' n Nothing Nothing) s
else
panic "node has not type Team"
-- TODO delete node, if not owned, then suppress the link only -- TODO delete node, if not owned, then suppress the link only
......
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